Added stop criterion on residual for BJAC as coarse solver

stopcriterion
Cirdans-Home 5 years ago
parent 70a85c6972
commit 6ac3e6c146

@ -40,6 +40,9 @@ mld_c_jac_smoother_descr.o \
mld_c_jac_smoother_dmp.o \ mld_c_jac_smoother_dmp.o \
mld_c_jac_smoother_clone.o \ mld_c_jac_smoother_clone.o \
mld_c_jac_smoother_cnv.o \ mld_c_jac_smoother_cnv.o \
mld_c_jac_smoother_csetc.o \
mld_c_jac_smoother_cseti.o \
mld_c_jac_smoother_csetr.o \
mld_d_as_smoother_apply.o \ mld_d_as_smoother_apply.o \
mld_d_as_smoother_apply_vect.o \ mld_d_as_smoother_apply_vect.o \
mld_d_as_smoother_bld.o \ mld_d_as_smoother_bld.o \
@ -73,6 +76,9 @@ mld_d_jac_smoother_descr.o \
mld_d_jac_smoother_dmp.o \ mld_d_jac_smoother_dmp.o \
mld_d_jac_smoother_clone.o \ mld_d_jac_smoother_clone.o \
mld_d_jac_smoother_cnv.o \ mld_d_jac_smoother_cnv.o \
mld_d_jac_smoother_csetc.o \
mld_d_jac_smoother_cseti.o \
mld_d_jac_smoother_csetr.o \
mld_s_as_smoother_apply.o \ mld_s_as_smoother_apply.o \
mld_s_as_smoother_apply_vect.o \ mld_s_as_smoother_apply_vect.o \
mld_s_as_smoother_bld.o \ mld_s_as_smoother_bld.o \
@ -106,6 +112,9 @@ mld_s_jac_smoother_descr.o \
mld_s_jac_smoother_dmp.o \ mld_s_jac_smoother_dmp.o \
mld_s_jac_smoother_clone.o \ mld_s_jac_smoother_clone.o \
mld_s_jac_smoother_cnv.o \ mld_s_jac_smoother_cnv.o \
mld_s_jac_smoother_csetc.o \
mld_s_jac_smoother_cseti.o \
mld_s_jac_smoother_csetr.o \
mld_z_as_smoother_apply.o \ mld_z_as_smoother_apply.o \
mld_z_as_smoother_apply_vect.o \ mld_z_as_smoother_apply_vect.o \
mld_z_as_smoother_bld.o \ mld_z_as_smoother_bld.o \
@ -138,7 +147,10 @@ mld_z_jac_smoother_bld.o \
mld_z_jac_smoother_descr.o \ mld_z_jac_smoother_descr.o \
mld_z_jac_smoother_dmp.o \ mld_z_jac_smoother_dmp.o \
mld_z_jac_smoother_clone.o \ mld_z_jac_smoother_clone.o \
mld_z_jac_smoother_cnv.o mld_z_jac_smoother_cnv.o \
mld_z_jac_smoother_csetc.o \
mld_z_jac_smoother_cseti.o \
mld_z_jac_smoother_csetr.o
LIBNAME=libmld_prec.a LIBNAME=libmld_prec.a
@ -155,4 +167,3 @@ veryclean: clean
clean: clean:
/bin/rm -f $(OBJS) $(LOCAL_MODS) /bin/rm -f $(OBJS) $(LOCAL_MODS)

@ -39,6 +39,7 @@ subroutine mld_c_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
& sweeps,work,wv,info,init,initu) & sweeps,work,wv,info,init,initu)
use psb_base_mod use psb_base_mod
use psb_base_krylov_conv_mod
use mld_c_jac_smoother, mld_protect_name => mld_c_jac_smoother_apply_vect use mld_c_jac_smoother, mld_protect_name => mld_c_jac_smoother_apply_vect
implicit none implicit none
type(psb_desc_type), intent(in) :: desc_data type(psb_desc_type), intent(in) :: desc_data
@ -55,10 +56,11 @@ subroutine mld_c_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
type(psb_c_vect_type),intent(inout), optional :: initu type(psb_c_vect_type),intent(inout), optional :: initu
! !
integer(psb_ipk_) :: n_row,n_col integer(psb_ipk_) :: n_row,n_col
type(psb_c_vect_type) :: tx, ty type(psb_c_vect_type) :: tx, ty, r
complex(psb_spk_), pointer :: aux(:) complex(psb_spk_), pointer :: aux(:)
integer(psb_ipk_) :: ictxt,np,me,i, err_act integer(psb_ipk_) :: ictxt,np,me,i, err_act
character :: trans_, init_ character :: trans_, init_
real(psb_dpk_) :: res, resdenum
character(len=20) :: name='c_jac_smoother_apply_v' character(len=20) :: name='c_jac_smoother_apply_v'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -105,6 +107,12 @@ subroutine mld_c_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
end if end if
endif endif
if(sm%checkres) then
call psb_geall(r,desc_data,info)
call psb_geasb(r,desc_data,info)
resdenum = psb_genrm2(x,desc_data,info)
end if
if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then
! if .not.sv%is_iterative, there's no need to pass init ! if .not.sv%is_iterative, there's no need to pass init
call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info) call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info)
@ -162,6 +170,20 @@ subroutine mld_c_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(cone,tx,cone,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(cone,tx,cone,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(cone,x,czero,r,r,desc_data,info)
call psb_spmm(-cone,sm%pa,ty,cone,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
@ -239,6 +261,20 @@ subroutine mld_c_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(cone,tx,czero,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(cone,tx,czero,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(cone,x,czero,r,r,desc_data,info)
call psb_spmm(-cone,sm%pa,ty,cone,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info) if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info)
@ -266,6 +302,10 @@ subroutine mld_c_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
deallocate(aux) deallocate(aux)
endif endif
if(sm%checkres) then
call psb_gefree(r,desc_data,info)
end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -71,6 +71,9 @@ subroutine mld_c_jac_smoother_bld(a,desc_a,sm,info,amold,vmold,imold)
n_col = desc_a%get_local_cols() n_col = desc_a%get_local_cols()
nrow_a = a%get_nrows() nrow_a = a%get_nrows()
nztota = a%get_nzeros() nztota = a%get_nzeros()
if( sm%checkres ) sm%pa => a
select type (smsv => sm%sv) select type (smsv => sm%sv)
class is (mld_c_diag_solver_type) class is (mld_c_diag_solver_type)
call sm%nd%free() call sm%nd%free()

@ -0,0 +1,85 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_c_jac_smoother_csetc(sm,what,val,info,idx)
use psb_base_mod
use mld_c_jac_smoother, mld_protect_nam => mld_c_jac_smoother_csetc
Implicit None
! Arguments
class(mld_c_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act, ival
character(len=20) :: name='c_jac_smoother_csetc'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOP')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%checkres = .true.
else
sm%checkres = .false.
end if
case('SMOOTHER_TRACE')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%printres = .true.
else
sm%printres = .false.
end if
case default
call sm%mld_c_base_smoother_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then
info = psb_err_from_subroutine_
call psb_errpush(info, name)
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_c_jac_smoother_csetc

@ -0,0 +1,71 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_c_jac_smoother_cseti(sm,what,val,info,idx)
use psb_base_mod
use mld_c_jac_smoother, mld_protect_nam => mld_c_jac_smoother_cseti
Implicit None
! Arguments
class(mld_c_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='c_jac_smoother_cseti'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_RESIDUAL')
sm%checkiter = val
case('SMOOTHER_ITRACE')
sm%printiter = val
case default
call sm%mld_c_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_c_jac_smoother_cseti

@ -0,0 +1,69 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_c_jac_smoother_csetr(sm,what,val,info,idx)
use psb_base_mod
use mld_c_jac_smoother, mld_protect_nam => mld_c_jac_smoother_csetr
Implicit None
! Arguments
class(mld_c_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_spk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='c_jac_smoother_csetr'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOPTOL')
sm%tol = val
case default
call sm%mld_c_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_c_jac_smoother_csetr

@ -39,6 +39,7 @@ subroutine mld_d_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
& sweeps,work,wv,info,init,initu) & sweeps,work,wv,info,init,initu)
use psb_base_mod use psb_base_mod
use psb_base_krylov_conv_mod
use mld_d_jac_smoother, mld_protect_name => mld_d_jac_smoother_apply_vect use mld_d_jac_smoother, mld_protect_name => mld_d_jac_smoother_apply_vect
implicit none implicit none
type(psb_desc_type), intent(in) :: desc_data type(psb_desc_type), intent(in) :: desc_data
@ -55,10 +56,11 @@ subroutine mld_d_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
type(psb_d_vect_type),intent(inout), optional :: initu type(psb_d_vect_type),intent(inout), optional :: initu
! !
integer(psb_ipk_) :: n_row,n_col integer(psb_ipk_) :: n_row,n_col
type(psb_d_vect_type) :: tx, ty type(psb_d_vect_type) :: tx, ty, r
real(psb_dpk_), pointer :: aux(:) real(psb_dpk_), pointer :: aux(:)
integer(psb_ipk_) :: ictxt,np,me,i, err_act integer(psb_ipk_) :: ictxt,np,me,i, err_act
character :: trans_, init_ character :: trans_, init_
real(psb_dpk_) :: res, resdenum
character(len=20) :: name='d_jac_smoother_apply_v' character(len=20) :: name='d_jac_smoother_apply_v'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -105,6 +107,12 @@ subroutine mld_d_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
end if end if
endif endif
if(sm%checkres) then
call psb_geall(r,desc_data,info)
call psb_geasb(r,desc_data,info)
resdenum = psb_genrm2(x,desc_data,info)
end if
if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then
! if .not.sv%is_iterative, there's no need to pass init ! if .not.sv%is_iterative, there's no need to pass init
call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info) call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info)
@ -162,6 +170,20 @@ subroutine mld_d_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(done,tx,done,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(done,tx,done,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(done,x,dzero,r,r,desc_data,info)
call psb_spmm(-done,sm%pa,ty,done,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
@ -239,6 +261,20 @@ subroutine mld_d_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(done,tx,dzero,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(done,tx,dzero,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(done,x,dzero,r,r,desc_data,info)
call psb_spmm(-done,sm%pa,ty,done,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info) if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info)
@ -266,6 +302,10 @@ subroutine mld_d_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
deallocate(aux) deallocate(aux)
endif endif
if(sm%checkres) then
call psb_gefree(r,desc_data,info)
end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -71,6 +71,9 @@ subroutine mld_d_jac_smoother_bld(a,desc_a,sm,info,amold,vmold,imold)
n_col = desc_a%get_local_cols() n_col = desc_a%get_local_cols()
nrow_a = a%get_nrows() nrow_a = a%get_nrows()
nztota = a%get_nzeros() nztota = a%get_nzeros()
if( sm%checkres ) sm%pa => a
select type (smsv => sm%sv) select type (smsv => sm%sv)
class is (mld_d_diag_solver_type) class is (mld_d_diag_solver_type)
call sm%nd%free() call sm%nd%free()

@ -0,0 +1,85 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_d_jac_smoother_csetc(sm,what,val,info,idx)
use psb_base_mod
use mld_d_jac_smoother, mld_protect_nam => mld_d_jac_smoother_csetc
Implicit None
! Arguments
class(mld_d_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act, ival
character(len=20) :: name='d_jac_smoother_csetc'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOP')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%checkres = .true.
else
sm%checkres = .false.
end if
case('SMOOTHER_TRACE')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%printres = .true.
else
sm%printres = .false.
end if
case default
call sm%mld_d_base_smoother_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then
info = psb_err_from_subroutine_
call psb_errpush(info, name)
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_d_jac_smoother_csetc

@ -0,0 +1,71 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_d_jac_smoother_cseti(sm,what,val,info,idx)
use psb_base_mod
use mld_d_jac_smoother, mld_protect_nam => mld_d_jac_smoother_cseti
Implicit None
! Arguments
class(mld_d_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='d_jac_smoother_cseti'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_RESIDUAL')
sm%checkiter = val
case('SMOOTHER_ITRACE')
sm%printiter = val
case default
call sm%mld_d_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_d_jac_smoother_cseti

@ -0,0 +1,69 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_d_jac_smoother_csetr(sm,what,val,info,idx)
use psb_base_mod
use mld_d_jac_smoother, mld_protect_nam => mld_d_jac_smoother_csetr
Implicit None
! Arguments
class(mld_d_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_dpk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='d_jac_smoother_csetr'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOPTOL')
sm%tol = val
case default
call sm%mld_d_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_d_jac_smoother_csetr

@ -39,6 +39,7 @@ subroutine mld_s_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
& sweeps,work,wv,info,init,initu) & sweeps,work,wv,info,init,initu)
use psb_base_mod use psb_base_mod
use psb_base_krylov_conv_mod
use mld_s_jac_smoother, mld_protect_name => mld_s_jac_smoother_apply_vect use mld_s_jac_smoother, mld_protect_name => mld_s_jac_smoother_apply_vect
implicit none implicit none
type(psb_desc_type), intent(in) :: desc_data type(psb_desc_type), intent(in) :: desc_data
@ -55,10 +56,11 @@ subroutine mld_s_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
type(psb_s_vect_type),intent(inout), optional :: initu type(psb_s_vect_type),intent(inout), optional :: initu
! !
integer(psb_ipk_) :: n_row,n_col integer(psb_ipk_) :: n_row,n_col
type(psb_s_vect_type) :: tx, ty type(psb_s_vect_type) :: tx, ty, r
real(psb_spk_), pointer :: aux(:) real(psb_spk_), pointer :: aux(:)
integer(psb_ipk_) :: ictxt,np,me,i, err_act integer(psb_ipk_) :: ictxt,np,me,i, err_act
character :: trans_, init_ character :: trans_, init_
real(psb_dpk_) :: res, resdenum
character(len=20) :: name='s_jac_smoother_apply_v' character(len=20) :: name='s_jac_smoother_apply_v'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -105,6 +107,12 @@ subroutine mld_s_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
end if end if
endif endif
if(sm%checkres) then
call psb_geall(r,desc_data,info)
call psb_geasb(r,desc_data,info)
resdenum = psb_genrm2(x,desc_data,info)
end if
if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then
! if .not.sv%is_iterative, there's no need to pass init ! if .not.sv%is_iterative, there's no need to pass init
call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info) call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info)
@ -162,6 +170,20 @@ subroutine mld_s_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(sone,tx,sone,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(sone,tx,sone,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(sone,x,szero,r,r,desc_data,info)
call psb_spmm(-sone,sm%pa,ty,sone,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
@ -239,6 +261,20 @@ subroutine mld_s_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(sone,tx,szero,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(sone,tx,szero,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(sone,x,szero,r,r,desc_data,info)
call psb_spmm(-sone,sm%pa,ty,sone,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info) if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info)
@ -266,6 +302,10 @@ subroutine mld_s_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
deallocate(aux) deallocate(aux)
endif endif
if(sm%checkres) then
call psb_gefree(r,desc_data,info)
end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -71,6 +71,9 @@ subroutine mld_s_jac_smoother_bld(a,desc_a,sm,info,amold,vmold,imold)
n_col = desc_a%get_local_cols() n_col = desc_a%get_local_cols()
nrow_a = a%get_nrows() nrow_a = a%get_nrows()
nztota = a%get_nzeros() nztota = a%get_nzeros()
if( sm%checkres ) sm%pa => a
select type (smsv => sm%sv) select type (smsv => sm%sv)
class is (mld_s_diag_solver_type) class is (mld_s_diag_solver_type)
call sm%nd%free() call sm%nd%free()

@ -0,0 +1,85 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_s_jac_smoother_csetc(sm,what,val,info,idx)
use psb_base_mod
use mld_s_jac_smoother, mld_protect_nam => mld_s_jac_smoother_csetc
Implicit None
! Arguments
class(mld_s_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act, ival
character(len=20) :: name='s_jac_smoother_csetc'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOP')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%checkres = .true.
else
sm%checkres = .false.
end if
case('SMOOTHER_TRACE')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%printres = .true.
else
sm%printres = .false.
end if
case default
call sm%mld_s_base_smoother_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then
info = psb_err_from_subroutine_
call psb_errpush(info, name)
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_s_jac_smoother_csetc

@ -0,0 +1,71 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_s_jac_smoother_cseti(sm,what,val,info,idx)
use psb_base_mod
use mld_s_jac_smoother, mld_protect_nam => mld_s_jac_smoother_cseti
Implicit None
! Arguments
class(mld_s_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='s_jac_smoother_cseti'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_RESIDUAL')
sm%checkiter = val
case('SMOOTHER_ITRACE')
sm%printiter = val
case default
call sm%mld_s_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_s_jac_smoother_cseti

@ -0,0 +1,69 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_s_jac_smoother_csetr(sm,what,val,info,idx)
use psb_base_mod
use mld_s_jac_smoother, mld_protect_nam => mld_s_jac_smoother_csetr
Implicit None
! Arguments
class(mld_s_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_spk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='s_jac_smoother_csetr'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOPTOL')
sm%tol = val
case default
call sm%mld_s_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_s_jac_smoother_csetr

@ -39,6 +39,7 @@ subroutine mld_z_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
& sweeps,work,wv,info,init,initu) & sweeps,work,wv,info,init,initu)
use psb_base_mod use psb_base_mod
use psb_base_krylov_conv_mod
use mld_z_jac_smoother, mld_protect_name => mld_z_jac_smoother_apply_vect use mld_z_jac_smoother, mld_protect_name => mld_z_jac_smoother_apply_vect
implicit none implicit none
type(psb_desc_type), intent(in) :: desc_data type(psb_desc_type), intent(in) :: desc_data
@ -55,10 +56,11 @@ subroutine mld_z_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
type(psb_z_vect_type),intent(inout), optional :: initu type(psb_z_vect_type),intent(inout), optional :: initu
! !
integer(psb_ipk_) :: n_row,n_col integer(psb_ipk_) :: n_row,n_col
type(psb_z_vect_type) :: tx, ty type(psb_z_vect_type) :: tx, ty, r
complex(psb_dpk_), pointer :: aux(:) complex(psb_dpk_), pointer :: aux(:)
integer(psb_ipk_) :: ictxt,np,me,i, err_act integer(psb_ipk_) :: ictxt,np,me,i, err_act
character :: trans_, init_ character :: trans_, init_
real(psb_dpk_) :: res, resdenum
character(len=20) :: name='z_jac_smoother_apply_v' character(len=20) :: name='z_jac_smoother_apply_v'
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -105,6 +107,12 @@ subroutine mld_z_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
end if end if
endif endif
if(sm%checkres) then
call psb_geall(r,desc_data,info)
call psb_geasb(r,desc_data,info)
resdenum = psb_genrm2(x,desc_data,info)
end if
if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then if ((.not.sm%sv%is_iterative()).and.((sweeps == 1).or.(sm%nd_nnz_tot==0))) then
! if .not.sv%is_iterative, there's no need to pass init ! if .not.sv%is_iterative, there's no need to pass init
call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info) call sm%sv%apply(alpha,x,beta,y,desc_data,trans_,aux,wv,info)
@ -162,6 +170,20 @@ subroutine mld_z_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(zone,tx,zone,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(zone,tx,zone,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(zone,x,zzero,r,r,desc_data,info)
call psb_spmm(-zone,sm%pa,ty,zone,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
@ -239,6 +261,20 @@ subroutine mld_z_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
call sm%sv%apply(zone,tx,zzero,ty,desc_data,trans_,aux,wv(3:),info,init='Y') call sm%sv%apply(zone,tx,zzero,ty,desc_data,trans_,aux,wv(3:),info,init='Y')
if (info /= psb_success_) exit if (info /= psb_success_) exit
if ( sm%checkres.and.(mod(i,sm%checkiter) == 0) ) then
call psb_geaxpby(zone,x,zzero,r,r,desc_data,info)
call psb_spmm(-zone,sm%pa,ty,zone,r,desc_data,info)
res = psb_genrm2(r,desc_data,info)
if( sm%printres ) then
call log_conv("BJAC",me,i,sm%printiter,res,resdenum,sm%tol)
end if
if (res/resdenum < sm%tol) then
if( sm%printres ) call log_conv("BJAC",me,i,1,res,resdenum,sm%tol)
exit
end if
end if
end do end do
if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info) if (info == psb_success_) call psb_geaxpby(alpha,ty,beta,y,desc_data,info)
@ -266,6 +302,10 @@ subroutine mld_z_jac_smoother_apply_vect(alpha,sm,x,beta,y,desc_data,trans,&
deallocate(aux) deallocate(aux)
endif endif
if(sm%checkres) then
call psb_gefree(r,desc_data,info)
end if
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -71,6 +71,9 @@ subroutine mld_z_jac_smoother_bld(a,desc_a,sm,info,amold,vmold,imold)
n_col = desc_a%get_local_cols() n_col = desc_a%get_local_cols()
nrow_a = a%get_nrows() nrow_a = a%get_nrows()
nztota = a%get_nzeros() nztota = a%get_nzeros()
if( sm%checkres ) sm%pa => a
select type (smsv => sm%sv) select type (smsv => sm%sv)
class is (mld_z_diag_solver_type) class is (mld_z_diag_solver_type)
call sm%nd%free() call sm%nd%free()

@ -0,0 +1,85 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_z_jac_smoother_csetc(sm,what,val,info,idx)
use psb_base_mod
use mld_z_jac_smoother, mld_protect_nam => mld_z_jac_smoother_csetc
Implicit None
! Arguments
class(mld_z_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act, ival
character(len=20) :: name='z_jac_smoother_csetc'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOP')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%checkres = .true.
else
sm%checkres = .false.
end if
case('SMOOTHER_TRACE')
if((trim(val) == 'T').or.(trim(val) == 'true')) then
sm%printres = .true.
else
sm%printres = .false.
end if
case default
call sm%mld_z_base_smoother_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then
info = psb_err_from_subroutine_
call psb_errpush(info, name)
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_z_jac_smoother_csetc

@ -0,0 +1,71 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_z_jac_smoother_cseti(sm,what,val,info,idx)
use psb_base_mod
use mld_z_jac_smoother, mld_protect_nam => mld_z_jac_smoother_cseti
Implicit None
! Arguments
class(mld_z_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='z_jac_smoother_cseti'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_RESIDUAL')
sm%checkiter = val
case('SMOOTHER_ITRACE')
sm%printiter = val
case default
call sm%mld_z_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_z_jac_smoother_cseti

@ -0,0 +1,69 @@
!
!
! MLD2P4 version 2.2
! MultiLevel Domain Decomposition Parallel Preconditioners Package
! based on PSBLAS (Parallel Sparse BLAS version 3.5)
!
! (C) Copyright 2008-2018
!
! Salvatore Filippone
! Pasqua D'Ambra
! Daniela di Serafino
!
! Redistribution and use in source and binary forms, with or without
! modification, are permitted provided that the following conditions
! are met:
! 1. Redistributions of source code must retain the above copyright
! notice, this list of conditions and the following disclaimer.
! 2. Redistributions in binary form must reproduce the above copyright
! notice, this list of conditions, and the following disclaimer in the
! documentation and/or other materials provided with the distribution.
! 3. The name of the MLD2P4 group or the names of its contributors may
! not be used to endorse or promote products derived from this
! software without specific written permission.
!
! THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
! ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
! TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
! PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE MLD2P4 GROUP OR ITS CONTRIBUTORS
! BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR
! CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF
! SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS
! INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN
! CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE)
! ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
! POSSIBILITY OF SUCH DAMAGE.
!
!
subroutine mld_z_jac_smoother_csetr(sm,what,val,info,idx)
use psb_base_mod
use mld_z_jac_smoother, mld_protect_nam => mld_z_jac_smoother_csetr
Implicit None
! Arguments
class(mld_z_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_dpk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
integer(psb_ipk_) :: err_act
character(len=20) :: name='z_jac_smoother_csetr'
info = psb_success_
call psb_erractionsave(err_act)
select case(psb_toupper(what))
case('SMOOTHER_STOPTOL')
sm%tol = val
case default
call sm%mld_z_base_smoother_type%set(what,val,info,idx=idx)
end select
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_z_jac_smoother_csetr

@ -61,6 +61,11 @@ module mld_c_jac_smoother
type(psb_cspmat_type), pointer :: pa => null() type(psb_cspmat_type), pointer :: pa => null()
type(psb_cspmat_type) :: nd type(psb_cspmat_type) :: nd
integer(psb_lpk_) :: nd_nnz_tot integer(psb_lpk_) :: nd_nnz_tot
logical :: checkres
logical :: printres
integer(psb_ipk_) :: checkiter
integer(psb_ipk_) :: printiter
real(psb_dpk_) :: tol
contains contains
procedure, pass(sm) :: dump => mld_c_jac_smoother_dmp procedure, pass(sm) :: dump => mld_c_jac_smoother_dmp
procedure, pass(sm) :: build => mld_c_jac_smoother_bld procedure, pass(sm) :: build => mld_c_jac_smoother_bld
@ -69,6 +74,9 @@ module mld_c_jac_smoother
procedure, pass(sm) :: apply_v => mld_c_jac_smoother_apply_vect procedure, pass(sm) :: apply_v => mld_c_jac_smoother_apply_vect
procedure, pass(sm) :: apply_a => mld_c_jac_smoother_apply procedure, pass(sm) :: apply_a => mld_c_jac_smoother_apply
procedure, pass(sm) :: free => c_jac_smoother_free procedure, pass(sm) :: free => c_jac_smoother_free
procedure, pass(sm) :: cseti => mld_c_jac_smoother_cseti
procedure, pass(sm) :: csetc => mld_c_jac_smoother_csetc
procedure, pass(sm) :: csetr => mld_c_jac_smoother_csetr
procedure, pass(sm) :: descr => mld_c_jac_smoother_descr procedure, pass(sm) :: descr => mld_c_jac_smoother_descr
procedure, pass(sm) :: sizeof => c_jac_smoother_sizeof procedure, pass(sm) :: sizeof => c_jac_smoother_sizeof
procedure, pass(sm) :: get_nzeros => c_jac_smoother_get_nzeros procedure, pass(sm) :: get_nzeros => c_jac_smoother_get_nzeros
@ -189,6 +197,45 @@ module mld_c_jac_smoother
end subroutine mld_c_jac_smoother_descr end subroutine mld_c_jac_smoother_descr
end interface end interface
interface
subroutine mld_c_jac_smoother_cseti(sm,what,val,info,idx)
import :: psb_cspmat_type, psb_c_vect_type, psb_c_base_vect_type, &
& psb_spk_, mld_c_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_c_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_c_jac_smoother_cseti
end interface
interface
subroutine mld_c_jac_smoother_csetc(sm,what,val,info,idx)
import :: psb_cspmat_type, psb_c_vect_type, psb_c_base_vect_type, &
& psb_spk_, mld_c_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_c_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_c_jac_smoother_csetc
end interface
interface
subroutine mld_c_jac_smoother_csetr(sm,what,val,info,idx)
import :: psb_cspmat_type, psb_c_vect_type, psb_c_base_vect_type, &
& psb_spk_, mld_c_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_c_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_spk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_c_jac_smoother_csetr
end interface
contains contains

@ -61,6 +61,11 @@ module mld_d_jac_smoother
type(psb_dspmat_type), pointer :: pa => null() type(psb_dspmat_type), pointer :: pa => null()
type(psb_dspmat_type) :: nd type(psb_dspmat_type) :: nd
integer(psb_lpk_) :: nd_nnz_tot integer(psb_lpk_) :: nd_nnz_tot
logical :: checkres
logical :: printres
integer(psb_ipk_) :: checkiter
integer(psb_ipk_) :: printiter
real(psb_dpk_) :: tol
contains contains
procedure, pass(sm) :: dump => mld_d_jac_smoother_dmp procedure, pass(sm) :: dump => mld_d_jac_smoother_dmp
procedure, pass(sm) :: build => mld_d_jac_smoother_bld procedure, pass(sm) :: build => mld_d_jac_smoother_bld
@ -69,6 +74,9 @@ module mld_d_jac_smoother
procedure, pass(sm) :: apply_v => mld_d_jac_smoother_apply_vect procedure, pass(sm) :: apply_v => mld_d_jac_smoother_apply_vect
procedure, pass(sm) :: apply_a => mld_d_jac_smoother_apply procedure, pass(sm) :: apply_a => mld_d_jac_smoother_apply
procedure, pass(sm) :: free => d_jac_smoother_free procedure, pass(sm) :: free => d_jac_smoother_free
procedure, pass(sm) :: cseti => mld_d_jac_smoother_cseti
procedure, pass(sm) :: csetc => mld_d_jac_smoother_csetc
procedure, pass(sm) :: csetr => mld_d_jac_smoother_csetr
procedure, pass(sm) :: descr => mld_d_jac_smoother_descr procedure, pass(sm) :: descr => mld_d_jac_smoother_descr
procedure, pass(sm) :: sizeof => d_jac_smoother_sizeof procedure, pass(sm) :: sizeof => d_jac_smoother_sizeof
procedure, pass(sm) :: get_nzeros => d_jac_smoother_get_nzeros procedure, pass(sm) :: get_nzeros => d_jac_smoother_get_nzeros
@ -189,6 +197,45 @@ module mld_d_jac_smoother
end subroutine mld_d_jac_smoother_descr end subroutine mld_d_jac_smoother_descr
end interface end interface
interface
subroutine mld_d_jac_smoother_cseti(sm,what,val,info,idx)
import :: psb_dspmat_type, psb_d_vect_type, psb_d_base_vect_type, &
& psb_dpk_, mld_d_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_d_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_d_jac_smoother_cseti
end interface
interface
subroutine mld_d_jac_smoother_csetc(sm,what,val,info,idx)
import :: psb_dspmat_type, psb_d_vect_type, psb_d_base_vect_type, &
& psb_dpk_, mld_d_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_d_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_d_jac_smoother_csetc
end interface
interface
subroutine mld_d_jac_smoother_csetr(sm,what,val,info,idx)
import :: psb_dspmat_type, psb_d_vect_type, psb_d_base_vect_type, &
& psb_dpk_, mld_d_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_d_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_dpk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_d_jac_smoother_csetr
end interface
contains contains

@ -61,6 +61,11 @@ module mld_s_jac_smoother
type(psb_sspmat_type), pointer :: pa => null() type(psb_sspmat_type), pointer :: pa => null()
type(psb_sspmat_type) :: nd type(psb_sspmat_type) :: nd
integer(psb_lpk_) :: nd_nnz_tot integer(psb_lpk_) :: nd_nnz_tot
logical :: checkres
logical :: printres
integer(psb_ipk_) :: checkiter
integer(psb_ipk_) :: printiter
real(psb_dpk_) :: tol
contains contains
procedure, pass(sm) :: dump => mld_s_jac_smoother_dmp procedure, pass(sm) :: dump => mld_s_jac_smoother_dmp
procedure, pass(sm) :: build => mld_s_jac_smoother_bld procedure, pass(sm) :: build => mld_s_jac_smoother_bld
@ -69,6 +74,9 @@ module mld_s_jac_smoother
procedure, pass(sm) :: apply_v => mld_s_jac_smoother_apply_vect procedure, pass(sm) :: apply_v => mld_s_jac_smoother_apply_vect
procedure, pass(sm) :: apply_a => mld_s_jac_smoother_apply procedure, pass(sm) :: apply_a => mld_s_jac_smoother_apply
procedure, pass(sm) :: free => s_jac_smoother_free procedure, pass(sm) :: free => s_jac_smoother_free
procedure, pass(sm) :: cseti => mld_s_jac_smoother_cseti
procedure, pass(sm) :: csetc => mld_s_jac_smoother_csetc
procedure, pass(sm) :: csetr => mld_s_jac_smoother_csetr
procedure, pass(sm) :: descr => mld_s_jac_smoother_descr procedure, pass(sm) :: descr => mld_s_jac_smoother_descr
procedure, pass(sm) :: sizeof => s_jac_smoother_sizeof procedure, pass(sm) :: sizeof => s_jac_smoother_sizeof
procedure, pass(sm) :: get_nzeros => s_jac_smoother_get_nzeros procedure, pass(sm) :: get_nzeros => s_jac_smoother_get_nzeros
@ -189,6 +197,45 @@ module mld_s_jac_smoother
end subroutine mld_s_jac_smoother_descr end subroutine mld_s_jac_smoother_descr
end interface end interface
interface
subroutine mld_s_jac_smoother_cseti(sm,what,val,info,idx)
import :: psb_sspmat_type, psb_s_vect_type, psb_s_base_vect_type, &
& psb_spk_, mld_s_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_s_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_s_jac_smoother_cseti
end interface
interface
subroutine mld_s_jac_smoother_csetc(sm,what,val,info,idx)
import :: psb_sspmat_type, psb_s_vect_type, psb_s_base_vect_type, &
& psb_spk_, mld_s_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_s_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_s_jac_smoother_csetc
end interface
interface
subroutine mld_s_jac_smoother_csetr(sm,what,val,info,idx)
import :: psb_sspmat_type, psb_s_vect_type, psb_s_base_vect_type, &
& psb_spk_, mld_s_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_s_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_spk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_s_jac_smoother_csetr
end interface
contains contains

@ -61,6 +61,11 @@ module mld_z_jac_smoother
type(psb_zspmat_type), pointer :: pa => null() type(psb_zspmat_type), pointer :: pa => null()
type(psb_zspmat_type) :: nd type(psb_zspmat_type) :: nd
integer(psb_lpk_) :: nd_nnz_tot integer(psb_lpk_) :: nd_nnz_tot
logical :: checkres
logical :: printres
integer(psb_ipk_) :: checkiter
integer(psb_ipk_) :: printiter
real(psb_dpk_) :: tol
contains contains
procedure, pass(sm) :: dump => mld_z_jac_smoother_dmp procedure, pass(sm) :: dump => mld_z_jac_smoother_dmp
procedure, pass(sm) :: build => mld_z_jac_smoother_bld procedure, pass(sm) :: build => mld_z_jac_smoother_bld
@ -69,6 +74,9 @@ module mld_z_jac_smoother
procedure, pass(sm) :: apply_v => mld_z_jac_smoother_apply_vect procedure, pass(sm) :: apply_v => mld_z_jac_smoother_apply_vect
procedure, pass(sm) :: apply_a => mld_z_jac_smoother_apply procedure, pass(sm) :: apply_a => mld_z_jac_smoother_apply
procedure, pass(sm) :: free => z_jac_smoother_free procedure, pass(sm) :: free => z_jac_smoother_free
procedure, pass(sm) :: cseti => mld_z_jac_smoother_cseti
procedure, pass(sm) :: csetc => mld_z_jac_smoother_csetc
procedure, pass(sm) :: csetr => mld_z_jac_smoother_csetr
procedure, pass(sm) :: descr => mld_z_jac_smoother_descr procedure, pass(sm) :: descr => mld_z_jac_smoother_descr
procedure, pass(sm) :: sizeof => z_jac_smoother_sizeof procedure, pass(sm) :: sizeof => z_jac_smoother_sizeof
procedure, pass(sm) :: get_nzeros => z_jac_smoother_get_nzeros procedure, pass(sm) :: get_nzeros => z_jac_smoother_get_nzeros
@ -189,6 +197,45 @@ module mld_z_jac_smoother
end subroutine mld_z_jac_smoother_descr end subroutine mld_z_jac_smoother_descr
end interface end interface
interface
subroutine mld_z_jac_smoother_cseti(sm,what,val,info,idx)
import :: psb_zspmat_type, psb_z_vect_type, psb_z_base_vect_type, &
& psb_dpk_, mld_z_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_z_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
integer(psb_ipk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_z_jac_smoother_cseti
end interface
interface
subroutine mld_z_jac_smoother_csetc(sm,what,val,info,idx)
import :: psb_zspmat_type, psb_z_vect_type, psb_z_base_vect_type, &
& psb_dpk_, mld_z_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_z_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_z_jac_smoother_csetc
end interface
interface
subroutine mld_z_jac_smoother_csetr(sm,what,val,info,idx)
import :: psb_zspmat_type, psb_z_vect_type, psb_z_base_vect_type, &
& psb_dpk_, mld_z_jac_smoother_type, psb_epk_, psb_desc_type, psb_ipk_
implicit none
class(mld_z_jac_smoother_type), intent(inout) :: sm
character(len=*), intent(in) :: what
real(psb_dpk_), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: idx
end subroutine mld_z_jac_smoother_csetr
end interface
contains contains

Loading…
Cancel
Save