mld2p4-2:

mlprec/mld_c_as_smoother.f90
 mlprec/mld_c_diag_solver.f90
 mlprec/mld_c_id_solver.f90
 mlprec/mld_c_ilu_solver.f90
 mlprec/mld_c_jac_smoother.f90
 mlprec/mld_c_prec_type.f90
 mlprec/mld_c_slu_solver.f90
 mlprec/mld_d_as_smoother.f90
 mlprec/mld_d_diag_solver.f90
 mlprec/mld_d_jac_smoother.f90
 mlprec/mld_d_prec_type.f90
 mlprec/mld_s_as_smoother.f90
 mlprec/mld_s_diag_solver.f90
 mlprec/mld_s_id_solver.f90
 mlprec/mld_s_ilu_solver.f90
 mlprec/mld_s_jac_smoother.f90
 mlprec/mld_s_prec_type.f90
 mlprec/mld_s_slu_solver.f90
 mlprec/mld_z_as_smoother.f90
 mlprec/mld_z_diag_solver.f90
 mlprec/mld_z_id_solver.f90
 mlprec/mld_z_ilu_solver.f90
 mlprec/mld_z_jac_smoother.f90
 mlprec/mld_z_prec_type.f90
 mlprec/mld_z_slu_solver.f90
 mlprec/mld_z_umf_solver.f90

Fixed coarse level description inconsistencies. Not complete, though.
stopcriterion
Salvatore Filippone 14 years ago
parent 01ef87b4ed
commit 1e3446e7c4

@ -328,7 +328,8 @@ contains
call sm%sv%apply(cone,tx,czero,ty,sm%desc_data,trans_,aux,info)
if (info /= psb_success_) then
call psb_errpush(psb_err_internal_error_,name,a_err='Error in sub_aply Jacobi Sweeps = 1')
call psb_errpush(psb_err_internal_error_,name,&
& a_err='Error in sub_aply Jacobi Sweeps = 1')
goto 9999
endif
@ -885,7 +886,7 @@ contains
return
end subroutine c_as_smoother_free
subroutine c_as_smoother_descr(sm,info,iout)
subroutine c_as_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -895,28 +896,37 @@ contains
class(mld_c_as_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
integer :: ictxt, me, np
character(len=20), parameter :: name='mld_c_as_smoother_descr'
integer :: iout_
logical :: coarse_
call psb_erractionsave(err_act)
info = psb_success_
if (present(coarse)) then
coarse_ = coarse
else
coarse_ = .false.
end if
if (present(iout)) then
iout_ = iout
else
iout_ = 6
endif
if (.not.coarse_) then
write(iout_,*) ' Additive Schwarz with ',&
& sm%novr, ' overlap layers.'
write(iout_,*) ' Restrictor: ',restrict_names(sm%restr)
write(iout_,*) ' Prolongator: ',prolong_names(sm%prol)
write(iout_,*) ' Local solver:'
endif
if (allocated(sm%sv)) then
call sm%sv%descr(info,iout_)
call sm%sv%descr(info,iout_,coarse=coarse)
end if
call psb_erractionrestore(err_act)

@ -419,7 +419,7 @@ contains
return
end subroutine c_diag_solver_free
subroutine c_diag_solver_descr(sv,info,iout)
subroutine c_diag_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -429,6 +429,7 @@ contains
class(mld_c_diag_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -234,7 +234,7 @@ contains
return
end subroutine c_id_solver_free
subroutine c_id_solver_descr(sv,info,iout)
subroutine c_id_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -244,6 +244,7 @@ contains
class(mld_c_id_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -608,7 +608,7 @@ contains
return
end subroutine c_ilu_solver_free
subroutine c_ilu_solver_descr(sv,info,iout)
subroutine c_ilu_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -618,6 +618,7 @@ contains
class(mld_c_ilu_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -459,7 +459,7 @@ contains
return
end subroutine c_jac_smoother_free
subroutine c_jac_smoother_descr(sm,info,iout)
subroutine c_jac_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -469,25 +469,34 @@ contains
class(mld_c_jac_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
integer :: ictxt, me, np
character(len=20), parameter :: name='mld_c_jac_smoother_descr'
integer :: iout_
logical :: coarse_
call psb_erractionsave(err_act)
info = psb_success_
if (present(coarse)) then
coarse_ = coarse
else
coarse_ = .false.
end if
if (present(iout)) then
iout_ = iout
else
iout_ = 6
endif
if (.not.coarse_) then
write(iout_,*) ' Block Jacobi smoother '
write(iout_,*) ' Local solver:'
end if
if (allocated(sm%sv)) then
call sm%sv%descr(info,iout_)
call sm%sv%descr(info,iout_,coarse=coarse)
end if
call psb_erractionrestore(err_act)

@ -520,7 +520,7 @@ contains
end if
end if
if (allocated(lv%sm)) &
& call lv%sm%descr(info,iout=iout_)
& call lv%sm%descr(info,iout=iout_,coarse=coarse)
call psb_erractionrestore(err_act)
return
@ -875,7 +875,7 @@ contains
return
end subroutine c_base_smoother_free
subroutine c_base_smoother_descr(sm,info,iout)
subroutine c_base_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -885,6 +885,7 @@ contains
class(mld_c_base_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
@ -1156,7 +1157,7 @@ contains
return
end subroutine c_base_solver_free
subroutine c_base_solver_descr(sv,info,iout)
subroutine c_base_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -1166,6 +1167,7 @@ contains
class(mld_c_base_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -409,7 +409,7 @@ contains
return
end subroutine c_slu_solver_free
subroutine c_slu_solver_descr(sv,info,iout)
subroutine c_slu_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -419,6 +419,7 @@ contains
class(mld_c_slu_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -326,8 +326,6 @@ contains
call sm%sv%apply(done,tx,dzero,ty,sm%desc_data,trans_,aux,info)
!!$ write(0,*) me,' out from inner slver in AS ',ty
if (info /= psb_success_) then
call psb_errpush(psb_err_internal_error_,name,&
& a_err='Error in sub_aply Jacobi Sweeps = 1')
@ -480,9 +478,9 @@ contains
call psb_spmm(-done,sm%nd,ty,done,ww,sm%desc_data,info,work=aux,trans=trans_)
if (info /= psb_success_) exit
!!$ write(0,*) me,' Entry to inner slver in AS-ND',ww
call sm%sv%apply(done,ww,dzero,ty,sm%desc_data,trans_,aux,info)
!!$ write(0,*) me,' Exit from inner slver in AS-ND ',ty
if (info /= psb_success_) exit

@ -419,7 +419,7 @@ contains
return
end subroutine d_diag_solver_free
subroutine d_diag_solver_descr(sv,info,iout)
subroutine d_diag_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -429,6 +429,7 @@ contains
class(mld_d_diag_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -270,12 +270,15 @@ contains
if (info == psb_success_) call sm%nd%cscnv(info,&
& type='csr',dupl=psb_dupl_add_)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,a_err='clip & psb_spcnv csr 4')
call psb_errpush(psb_err_from_subroutine_,name,&
& a_err='clip & psb_spcnv csr 4')
goto 9999
end if
call sm%sv%build(a,desc_a,upd,info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,a_err='solver_build')
call psb_errpush(psb_err_from_subroutine_,name,&
& a_err='solver build')
goto 9999
end if
nzeros = sm%nd%get_nzeros()
@ -454,7 +457,7 @@ contains
return
end subroutine d_jac_smoother_free
subroutine d_jac_smoother_descr(sm,info,iout)
subroutine d_jac_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -464,25 +467,34 @@ contains
class(mld_d_jac_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
integer :: ictxt, me, np
character(len=20), parameter :: name='mld_d_jac_smoother_descr'
integer :: iout_
logical :: coarse_
call psb_erractionsave(err_act)
info = psb_success_
if (present(coarse)) then
coarse_ = coarse
else
coarse_ = .false.
end if
if (present(iout)) then
iout_ = iout
else
iout_ = 6
endif
if (.not.coarse_) then
write(iout_,*) ' Block Jacobi smoother '
write(iout_,*) ' Local solver:'
end if
if (allocated(sm%sv)) then
call sm%sv%descr(info,iout_)
call sm%sv%descr(info,iout_,coarse=coarse)
end if
call psb_erractionrestore(err_act)

@ -313,7 +313,6 @@ contains
val = val + psb_sizeof_int
if (allocated(prec%precv)) then
do i=1, size(prec%precv)
!!$ write(0,*) 'At level ',i, mld_sizeof(prec%precv(i))
val = val + mld_sizeof(prec%precv(i))
end do
end if

@ -885,7 +885,7 @@ contains
return
end subroutine s_as_smoother_free
subroutine s_as_smoother_descr(sm,info,iout)
subroutine s_as_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -895,28 +895,37 @@ contains
class(mld_s_as_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
integer :: ictxt, me, np
character(len=20), parameter :: name='mld_s_as_smoother_descr'
integer :: iout_
logical :: coarse_
call psb_erractionsave(err_act)
info = psb_success_
if (present(coarse)) then
coarse_ = coarse
else
coarse_ = .false.
end if
if (present(iout)) then
iout_ = iout
else
iout_ = 6
endif
if (.not.coarse_) then
write(iout_,*) ' Additive Schwarz with ',&
& sm%novr, ' overlap layers.'
write(iout_,*) ' Restrictor: ',restrict_names(sm%restr)
write(iout_,*) ' Prolongator: ',prolong_names(sm%prol)
write(iout_,*) ' Local solver:'
endif
if (allocated(sm%sv)) then
call sm%sv%descr(info,iout_)
call sm%sv%descr(info,iout_,coarse=coarse)
end if
call psb_erractionrestore(err_act)

@ -419,7 +419,7 @@ contains
return
end subroutine s_diag_solver_free
subroutine s_diag_solver_descr(sv,info,iout)
subroutine s_diag_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -429,6 +429,7 @@ contains
class(mld_s_diag_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -234,7 +234,7 @@ contains
return
end subroutine s_id_solver_free
subroutine s_id_solver_descr(sv,info,iout)
subroutine s_id_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -244,6 +244,7 @@ contains
class(mld_s_id_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -608,7 +608,7 @@ contains
return
end subroutine s_ilu_solver_free
subroutine s_ilu_solver_descr(sv,info,iout)
subroutine s_ilu_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -618,6 +618,7 @@ contains
class(mld_s_ilu_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -457,7 +457,7 @@ contains
return
end subroutine s_jac_smoother_free
subroutine s_jac_smoother_descr(sm,info,iout)
subroutine s_jac_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -467,25 +467,34 @@ contains
class(mld_s_jac_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
integer :: ictxt, me, np
character(len=20), parameter :: name='mld_s_jac_smoother_descr'
integer :: iout_
logical :: coarse_
call psb_erractionsave(err_act)
info = psb_success_
if (present(coarse)) then
coarse_ = coarse
else
coarse_ = .false.
end if
if (present(iout)) then
iout_ = iout
else
iout_ = 6
endif
if (.not.coarse_) then
write(iout_,*) ' Block Jacobi smoother '
write(iout_,*) ' Local solver:'
end if
if (allocated(sm%sv)) then
call sm%sv%descr(info,iout_)
call sm%sv%descr(info,iout_,coarse=coarse)
end if
call psb_erractionrestore(err_act)

@ -521,7 +521,7 @@ contains
end if
end if
if (allocated(lv%sm)) &
& call lv%sm%descr(info,iout=iout_)
& call lv%sm%descr(info,iout=iout_,coarse=coarse)
call psb_erractionrestore(err_act)
return
@ -877,7 +877,7 @@ contains
return
end subroutine s_base_smoother_free
subroutine s_base_smoother_descr(sm,info,iout)
subroutine s_base_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -887,6 +887,7 @@ contains
class(mld_s_base_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
@ -1158,7 +1159,7 @@ contains
return
end subroutine s_base_solver_free
subroutine s_base_solver_descr(sv,info,iout)
subroutine s_base_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -1168,6 +1169,7 @@ contains
class(mld_s_base_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -407,7 +407,7 @@ contains
return
end subroutine s_slu_solver_free
subroutine s_slu_solver_descr(sv,info,iout)
subroutine s_slu_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -417,6 +417,7 @@ contains
class(mld_s_slu_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -328,7 +328,8 @@ contains
call sm%sv%apply(zone,tx,zzero,ty,sm%desc_data,trans_,aux,info)
if (info /= psb_success_) then
call psb_errpush(psb_err_internal_error_,name,a_err='Error in sub_aply Jacobi Sweeps = 1')
call psb_errpush(psb_err_internal_error_,name,&
& a_err='Error in sub_aply Jacobi Sweeps = 1')
goto 9999
endif
@ -885,7 +886,7 @@ contains
return
end subroutine z_as_smoother_free
subroutine z_as_smoother_descr(sm,info,iout)
subroutine z_as_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -895,28 +896,37 @@ contains
class(mld_z_as_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
integer :: ictxt, me, np
character(len=20), parameter :: name='mld_z_as_smoother_descr'
integer :: iout_
logical :: coarse_
call psb_erractionsave(err_act)
info = psb_success_
if (present(coarse)) then
coarse_ = coarse
else
coarse_ = .false.
end if
if (present(iout)) then
iout_ = iout
else
iout_ = 6
endif
if (.not.coarse_) then
write(iout_,*) ' Additive Schwarz with ',&
& sm%novr, ' overlap layers.'
write(iout_,*) ' Restrictor: ',restrict_names(sm%restr)
write(iout_,*) ' Prolongator: ',prolong_names(sm%prol)
write(iout_,*) ' Local solver:'
endif
if (allocated(sm%sv)) then
call sm%sv%descr(info,iout_)
call sm%sv%descr(info,iout_,coarse=coarse)
end if
call psb_erractionrestore(err_act)

@ -419,7 +419,7 @@ contains
return
end subroutine z_diag_solver_free
subroutine z_diag_solver_descr(sv,info,iout)
subroutine z_diag_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -429,6 +429,7 @@ contains
class(mld_z_diag_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -234,7 +234,7 @@ contains
return
end subroutine z_id_solver_free
subroutine z_id_solver_descr(sv,info,iout)
subroutine z_id_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -244,6 +244,7 @@ contains
class(mld_z_id_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -608,7 +608,7 @@ contains
return
end subroutine z_ilu_solver_free
subroutine z_ilu_solver_descr(sv,info,iout)
subroutine z_ilu_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -618,6 +618,7 @@ contains
class(mld_z_ilu_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -269,8 +269,6 @@ contains
end select
if (info == psb_success_) call sm%nd%cscnv(info,&
& type='csr',dupl=psb_dupl_add_)
if (info == psb_success_) &
& call sm%sv%build(a,desc_a,upd,info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,&
& a_err='clip & psb_spcnv csr 4')
@ -459,7 +457,7 @@ contains
return
end subroutine z_jac_smoother_free
subroutine z_jac_smoother_descr(sm,info,iout)
subroutine z_jac_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -469,25 +467,34 @@ contains
class(mld_z_jac_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
integer :: ictxt, me, np
character(len=20), parameter :: name='mld_z_jac_smoother_descr'
integer :: iout_
logical :: coarse_
call psb_erractionsave(err_act)
info = psb_success_
if (present(coarse)) then
coarse_ = coarse
else
coarse_ = .false.
end if
if (present(iout)) then
iout_ = iout
else
iout_ = 6
endif
if (.not.coarse_) then
write(iout_,*) ' Block Jacobi smoother '
write(iout_,*) ' Local solver:'
end if
if (allocated(sm%sv)) then
call sm%sv%descr(info,iout_)
call sm%sv%descr(info,iout_,coarse=coarse)
end if
call psb_erractionrestore(err_act)

@ -519,7 +519,7 @@ contains
end if
end if
if (allocated(lv%sm)) &
& call lv%sm%descr(info,iout=iout_)
& call lv%sm%descr(info,iout=iout_,coarse=coarse)
call psb_erractionrestore(err_act)
return
@ -874,7 +874,7 @@ contains
return
end subroutine z_base_smoother_free
subroutine z_base_smoother_descr(sm,info,iout)
subroutine z_base_smoother_descr(sm,info,iout,coarse)
use psb_sparse_mod
@ -884,6 +884,7 @@ contains
class(mld_z_base_smoother_type), intent(in) :: sm
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act
@ -1153,7 +1154,7 @@ contains
return
end subroutine z_base_solver_free
subroutine z_base_solver_descr(sv,info,iout)
subroutine z_base_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -1163,6 +1164,7 @@ contains
class(mld_z_base_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -409,7 +409,7 @@ contains
return
end subroutine z_slu_solver_free
subroutine z_slu_solver_descr(sv,info,iout)
subroutine z_slu_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -419,6 +419,7 @@ contains
class(mld_z_slu_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

@ -412,7 +412,7 @@ contains
return
end subroutine z_umf_solver_free
subroutine z_umf_solver_descr(sv,info,iout)
subroutine z_umf_solver_descr(sv,info,iout,coarse)
use psb_sparse_mod
@ -422,6 +422,7 @@ contains
class(mld_z_umf_solver_type), intent(in) :: sv
integer, intent(out) :: info
integer, intent(in), optional :: iout
logical, intent(in), optional :: coarse
! Local variables
integer :: err_act

Loading…
Cancel
Save