Reworked CSETC methods

pizdaint-runs
Salvatore Filippone 5 years ago
parent 4af1351344
commit 825037761f

@ -126,6 +126,7 @@ subroutine mld_c_base_onelev_build(lv,info,amold,vmold,imold,ilv)
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
if (me == 0) then if (me == 0) then
write(debug_unit,*)
if (present(ilv)) then if (present(ilv)) then
write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),& write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),&
& '" at level ',ilv & '" at level ',ilv

@ -0,0 +1,266 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_csetc
use mld_c_base_aggregator_mod
use mld_c_dec_aggregator_mod
use mld_c_symdec_aggregator_mod
use mld_c_jac_smoother
use mld_c_as_smoother
use mld_c_diag_solver
use mld_c_l1_diag_solver
use mld_c_ilu_solver
use mld_c_id_solver
use mld_c_gs_solver
#if defined(HAVE_SLU_)
use mld_c_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_c_mumps_solver
#endif
Implicit None
! Arguments
class(mld_c_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='c_base_onelev_csetc'
integer(psb_ipk_) :: ival
type(mld_c_base_smoother_type) :: mld_c_base_smoother_mold
type(mld_c_jac_smoother_type) :: mld_c_jac_smoother_mold
type(mld_c_as_smoother_type) :: mld_c_as_smoother_mold
type(mld_c_diag_solver_type) :: mld_c_diag_solver_mold
type(mld_c_l1_diag_solver_type) :: mld_c_l1_diag_solver_mold
type(mld_c_ilu_solver_type) :: mld_c_ilu_solver_mold
type(mld_c_id_solver_type) :: mld_c_id_solver_mold
type(mld_c_gs_solver_type) :: mld_c_gs_solver_mold
type(mld_c_bwgs_solver_type) :: mld_c_bwgs_solver_mold
#if defined(HAVE_SLU_)
type(mld_c_slu_solver_type) :: mld_c_slu_solver_mold
#endif
#if defined(HAVE_MUMPS_)
type(mld_c_mumps_solver_type) :: mld_c_mumps_solver_mold
#endif
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
select case (psb_toupper(trim(what)))
case ('SMOOTHER_TYPE')
select case (psb_toupper(trim(val)))
case ('NOPREC','NONE')
call lv%set(mld_c_base_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_c_id_solver_mold,info,pos=pos)
case ('JAC','JACOBI')
call lv%set(mld_c_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_c_diag_solver_mold,info,pos=pos)
case ('L1-JACOBI')
call lv%set(mld_c_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_c_l1_diag_solver_mold,info,pos=pos)
case ('BJAC')
call lv%set(mld_c_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_c_ilu_solver_mold,info,pos=pos)
case ('AS')
call lv%set(mld_c_as_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_c_ilu_solver_mold,info,pos=pos)
case ('FBGS')
call lv%set(mld_c_jac_smoother_mold,info,pos='pre')
if (info == 0) call lv%set(mld_c_gs_solver_mold,info,pos='pre')
call lv%set(mld_c_jac_smoother_mold,info,pos='post')
if (info == 0) call lv%set(mld_c_bwgs_solver_mold,info,pos='post')
case default
!
! Do nothing and hope for the best :)
!
end select
if ((ipos_==mld_smooth_pre_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) call lv%sm%default()
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm2a)) call lv%sm2a%default()
end if
case('SUB_SOLVE')
select case (psb_toupper(trim(val)))
case ('NONE','NOPREC','FACT_NONE')
call lv%set(mld_c_id_solver_mold,info,pos=pos)
case ('DIAG')
call lv%set(mld_c_diag_solver_mold,info,pos=pos)
case ('L1-DIAG')
call lv%set(mld_c_l1_diag_solver_mold,info,pos=pos)
case ('GS','FGS','FWGS')
call lv%set(mld_c_gs_solver_mold,info,pos=pos)
case ('BGS','BWGS')
call lv%set(mld_c_bwgs_solver_mold,info,pos=pos)
case ('ILU','ILUT','MILU')
call lv%set(mld_c_ilu_solver_mold,info,pos=pos)
if (info == 0) then
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
call lv%sm%sv%set('SUB_SOLVE',val,info)
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) call lv%sm2a%sv%set('SUB_SOLVE',val,info)
end if
end if
#ifdef HAVE_SLU_
case ('SLU')
call lv%set(mld_c_slu_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_MUMPS_
case ('MUMPS')
call lv%set(mld_c_mumps_solver_mold,info,pos=pos)
#endif
case default
!
! Do nothing and hope for the best :)
!
end select
case ('ML_CYCLE')
lv%parms%ml_cycle = mld_stringval(val)
case ('PAR_AGGR_ALG')
ival = mld_stringval(val)
lv%parms%par_aggr_alg = ival
if (allocated(lv%aggr)) then
call lv%aggr%free(info)
if (info == 0) deallocate(lv%aggr,stat=info)
if (info /= 0) then
info = psb_err_internal_error_
return
end if
end if
select case(ival)
case(mld_dec_aggr_)
allocate(mld_c_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_)
allocate(mld_c_symdec_aggregator_type :: lv%aggr, stat=info)
case default
info = psb_err_internal_error_
end select
if (info == psb_success_) call lv%aggr%default()
case ('AGGR_ORD')
lv%parms%aggr_ord = mld_stringval(val)
case ('AGGR_TYPE')
lv%parms%aggr_type = mld_stringval(val)
if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info)
case ('AGGR_PROL')
lv%parms%aggr_prol = mld_stringval(val)
case ('COARSE_MAT')
lv%parms%coarse_mat = mld_stringval(val)
case ('AGGR_OMEGA_ALG')
lv%parms%aggr_omega_alg= mld_stringval(val)
case ('AGGR_EIG')
lv%parms%aggr_eig = mld_stringval(val)
case ('AGGR_FILTER')
lv%parms%aggr_filter = mld_stringval(val)
case ('COARSE_SOLVE')
lv%parms%coarse_solve = mld_stringval(val)
case default
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_c_base_onelev_csetc

@ -1,103 +0,0 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_c_onelev_mod, mld_protect_name => mld_c_base_onelev_csetc
Implicit None
! Arguments
class(mld_c_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='c_base_onelev_csetc'
integer(psb_ipk_) :: ival
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (ival >= 0) then
call lv%set(what,ival,info,pos=pos)
else
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_c_base_onelev_csetc

@ -126,6 +126,7 @@ subroutine mld_d_base_onelev_build(lv,info,amold,vmold,imold,ilv)
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
if (me == 0) then if (me == 0) then
write(debug_unit,*)
if (present(ilv)) then if (present(ilv)) then
write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),& write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),&
& '" at level ',ilv & '" at level ',ilv

@ -0,0 +1,286 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_csetc
use mld_d_base_aggregator_mod
use mld_d_dec_aggregator_mod
use mld_d_symdec_aggregator_mod
use mld_d_jac_smoother
use mld_d_as_smoother
use mld_d_diag_solver
use mld_d_l1_diag_solver
use mld_d_ilu_solver
use mld_d_id_solver
use mld_d_gs_solver
#if defined(HAVE_UMF_)
use mld_d_umf_solver
#endif
#if defined(HAVE_SLUDIST_)
use mld_d_sludist_solver
#endif
#if defined(HAVE_SLU_)
use mld_d_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_d_mumps_solver
#endif
Implicit None
! Arguments
class(mld_d_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='d_base_onelev_csetc'
integer(psb_ipk_) :: ival
type(mld_d_base_smoother_type) :: mld_d_base_smoother_mold
type(mld_d_jac_smoother_type) :: mld_d_jac_smoother_mold
type(mld_d_as_smoother_type) :: mld_d_as_smoother_mold
type(mld_d_diag_solver_type) :: mld_d_diag_solver_mold
type(mld_d_l1_diag_solver_type) :: mld_d_l1_diag_solver_mold
type(mld_d_ilu_solver_type) :: mld_d_ilu_solver_mold
type(mld_d_id_solver_type) :: mld_d_id_solver_mold
type(mld_d_gs_solver_type) :: mld_d_gs_solver_mold
type(mld_d_bwgs_solver_type) :: mld_d_bwgs_solver_mold
#if defined(HAVE_UMF_)
type(mld_d_umf_solver_type) :: mld_d_umf_solver_mold
#endif
#if defined(HAVE_SLUDIST_)
type(mld_d_sludist_solver_type) :: mld_d_sludist_solver_mold
#endif
#if defined(HAVE_SLU_)
type(mld_d_slu_solver_type) :: mld_d_slu_solver_mold
#endif
#if defined(HAVE_MUMPS_)
type(mld_d_mumps_solver_type) :: mld_d_mumps_solver_mold
#endif
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
select case (psb_toupper(trim(what)))
case ('SMOOTHER_TYPE')
select case (psb_toupper(trim(val)))
case ('NOPREC','NONE')
call lv%set(mld_d_base_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_d_id_solver_mold,info,pos=pos)
case ('JAC','JACOBI')
call lv%set(mld_d_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_d_diag_solver_mold,info,pos=pos)
case ('L1-JACOBI')
call lv%set(mld_d_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_d_l1_diag_solver_mold,info,pos=pos)
case ('BJAC')
call lv%set(mld_d_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_d_ilu_solver_mold,info,pos=pos)
case ('AS')
call lv%set(mld_d_as_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_d_ilu_solver_mold,info,pos=pos)
case ('FBGS')
call lv%set(mld_d_jac_smoother_mold,info,pos='pre')
if (info == 0) call lv%set(mld_d_gs_solver_mold,info,pos='pre')
call lv%set(mld_d_jac_smoother_mold,info,pos='post')
if (info == 0) call lv%set(mld_d_bwgs_solver_mold,info,pos='post')
case default
!
! Do nothing and hope for the best :)
!
end select
if ((ipos_==mld_smooth_pre_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) call lv%sm%default()
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm2a)) call lv%sm2a%default()
end if
case('SUB_SOLVE')
select case (psb_toupper(trim(val)))
case ('NONE','NOPREC','FACT_NONE')
call lv%set(mld_d_id_solver_mold,info,pos=pos)
case ('DIAG')
call lv%set(mld_d_diag_solver_mold,info,pos=pos)
case ('L1-DIAG')
call lv%set(mld_d_l1_diag_solver_mold,info,pos=pos)
case ('GS','FGS','FWGS')
call lv%set(mld_d_gs_solver_mold,info,pos=pos)
case ('BGS','BWGS')
call lv%set(mld_d_bwgs_solver_mold,info,pos=pos)
case ('ILU','ILUT','MILU')
call lv%set(mld_d_ilu_solver_mold,info,pos=pos)
if (info == 0) then
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
call lv%sm%sv%set('SUB_SOLVE',val,info)
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) call lv%sm2a%sv%set('SUB_SOLVE',val,info)
end if
end if
#ifdef HAVE_SLU_
case ('SLU')
call lv%set(mld_d_slu_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_MUMPS_
case ('MUMPS')
call lv%set(mld_d_mumps_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_SLUDIST_
case ('SLUDIST')
call lv%set(mld_d_sludist_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_UMF_
case ('UMF')
call lv%set(mld_d_umf_solver_mold,info,pos=pos)
#endif
case default
!
! Do nothing and hope for the best :)
!
end select
case ('ML_CYCLE')
lv%parms%ml_cycle = mld_stringval(val)
case ('PAR_AGGR_ALG')
ival = mld_stringval(val)
lv%parms%par_aggr_alg = ival
if (allocated(lv%aggr)) then
call lv%aggr%free(info)
if (info == 0) deallocate(lv%aggr,stat=info)
if (info /= 0) then
info = psb_err_internal_error_
return
end if
end if
select case(ival)
case(mld_dec_aggr_)
allocate(mld_d_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_)
allocate(mld_d_symdec_aggregator_type :: lv%aggr, stat=info)
case default
info = psb_err_internal_error_
end select
if (info == psb_success_) call lv%aggr%default()
case ('AGGR_ORD')
lv%parms%aggr_ord = mld_stringval(val)
case ('AGGR_TYPE')
lv%parms%aggr_type = mld_stringval(val)
if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info)
case ('AGGR_PROL')
lv%parms%aggr_prol = mld_stringval(val)
case ('COARSE_MAT')
lv%parms%coarse_mat = mld_stringval(val)
case ('AGGR_OMEGA_ALG')
lv%parms%aggr_omega_alg= mld_stringval(val)
case ('AGGR_EIG')
lv%parms%aggr_eig = mld_stringval(val)
case ('AGGR_FILTER')
lv%parms%aggr_filter = mld_stringval(val)
case ('COARSE_SOLVE')
lv%parms%coarse_solve = mld_stringval(val)
case default
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_d_base_onelev_csetc

@ -1,103 +0,0 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_d_onelev_mod, mld_protect_name => mld_d_base_onelev_csetc
Implicit None
! Arguments
class(mld_d_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='d_base_onelev_csetc'
integer(psb_ipk_) :: ival
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (ival >= 0) then
call lv%set(what,ival,info,pos=pos)
else
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_d_base_onelev_csetc

@ -126,6 +126,7 @@ subroutine mld_s_base_onelev_build(lv,info,amold,vmold,imold,ilv)
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
if (me == 0) then if (me == 0) then
write(debug_unit,*)
if (present(ilv)) then if (present(ilv)) then
write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),& write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),&
& '" at level ',ilv & '" at level ',ilv

@ -0,0 +1,266 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_csetc
use mld_s_base_aggregator_mod
use mld_s_dec_aggregator_mod
use mld_s_symdec_aggregator_mod
use mld_s_jac_smoother
use mld_s_as_smoother
use mld_s_diag_solver
use mld_s_l1_diag_solver
use mld_s_ilu_solver
use mld_s_id_solver
use mld_s_gs_solver
#if defined(HAVE_SLU_)
use mld_s_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_s_mumps_solver
#endif
Implicit None
! Arguments
class(mld_s_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='s_base_onelev_csetc'
integer(psb_ipk_) :: ival
type(mld_s_base_smoother_type) :: mld_s_base_smoother_mold
type(mld_s_jac_smoother_type) :: mld_s_jac_smoother_mold
type(mld_s_as_smoother_type) :: mld_s_as_smoother_mold
type(mld_s_diag_solver_type) :: mld_s_diag_solver_mold
type(mld_s_l1_diag_solver_type) :: mld_s_l1_diag_solver_mold
type(mld_s_ilu_solver_type) :: mld_s_ilu_solver_mold
type(mld_s_id_solver_type) :: mld_s_id_solver_mold
type(mld_s_gs_solver_type) :: mld_s_gs_solver_mold
type(mld_s_bwgs_solver_type) :: mld_s_bwgs_solver_mold
#if defined(HAVE_SLU_)
type(mld_s_slu_solver_type) :: mld_s_slu_solver_mold
#endif
#if defined(HAVE_MUMPS_)
type(mld_s_mumps_solver_type) :: mld_s_mumps_solver_mold
#endif
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
select case (psb_toupper(trim(what)))
case ('SMOOTHER_TYPE')
select case (psb_toupper(trim(val)))
case ('NOPREC','NONE')
call lv%set(mld_s_base_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_s_id_solver_mold,info,pos=pos)
case ('JAC','JACOBI')
call lv%set(mld_s_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_s_diag_solver_mold,info,pos=pos)
case ('L1-JACOBI')
call lv%set(mld_s_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_s_l1_diag_solver_mold,info,pos=pos)
case ('BJAC')
call lv%set(mld_s_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_s_ilu_solver_mold,info,pos=pos)
case ('AS')
call lv%set(mld_s_as_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_s_ilu_solver_mold,info,pos=pos)
case ('FBGS')
call lv%set(mld_s_jac_smoother_mold,info,pos='pre')
if (info == 0) call lv%set(mld_s_gs_solver_mold,info,pos='pre')
call lv%set(mld_s_jac_smoother_mold,info,pos='post')
if (info == 0) call lv%set(mld_s_bwgs_solver_mold,info,pos='post')
case default
!
! Do nothing and hope for the best :)
!
end select
if ((ipos_==mld_smooth_pre_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) call lv%sm%default()
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm2a)) call lv%sm2a%default()
end if
case('SUB_SOLVE')
select case (psb_toupper(trim(val)))
case ('NONE','NOPREC','FACT_NONE')
call lv%set(mld_s_id_solver_mold,info,pos=pos)
case ('DIAG')
call lv%set(mld_s_diag_solver_mold,info,pos=pos)
case ('L1-DIAG')
call lv%set(mld_s_l1_diag_solver_mold,info,pos=pos)
case ('GS','FGS','FWGS')
call lv%set(mld_s_gs_solver_mold,info,pos=pos)
case ('BGS','BWGS')
call lv%set(mld_s_bwgs_solver_mold,info,pos=pos)
case ('ILU','ILUT','MILU')
call lv%set(mld_s_ilu_solver_mold,info,pos=pos)
if (info == 0) then
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
call lv%sm%sv%set('SUB_SOLVE',val,info)
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) call lv%sm2a%sv%set('SUB_SOLVE',val,info)
end if
end if
#ifdef HAVE_SLU_
case ('SLU')
call lv%set(mld_s_slu_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_MUMPS_
case ('MUMPS')
call lv%set(mld_s_mumps_solver_mold,info,pos=pos)
#endif
case default
!
! Do nothing and hope for the best :)
!
end select
case ('ML_CYCLE')
lv%parms%ml_cycle = mld_stringval(val)
case ('PAR_AGGR_ALG')
ival = mld_stringval(val)
lv%parms%par_aggr_alg = ival
if (allocated(lv%aggr)) then
call lv%aggr%free(info)
if (info == 0) deallocate(lv%aggr,stat=info)
if (info /= 0) then
info = psb_err_internal_error_
return
end if
end if
select case(ival)
case(mld_dec_aggr_)
allocate(mld_s_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_)
allocate(mld_s_symdec_aggregator_type :: lv%aggr, stat=info)
case default
info = psb_err_internal_error_
end select
if (info == psb_success_) call lv%aggr%default()
case ('AGGR_ORD')
lv%parms%aggr_ord = mld_stringval(val)
case ('AGGR_TYPE')
lv%parms%aggr_type = mld_stringval(val)
if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info)
case ('AGGR_PROL')
lv%parms%aggr_prol = mld_stringval(val)
case ('COARSE_MAT')
lv%parms%coarse_mat = mld_stringval(val)
case ('AGGR_OMEGA_ALG')
lv%parms%aggr_omega_alg= mld_stringval(val)
case ('AGGR_EIG')
lv%parms%aggr_eig = mld_stringval(val)
case ('AGGR_FILTER')
lv%parms%aggr_filter = mld_stringval(val)
case ('COARSE_SOLVE')
lv%parms%coarse_solve = mld_stringval(val)
case default
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_s_base_onelev_csetc

@ -1,103 +0,0 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_s_onelev_mod, mld_protect_name => mld_s_base_onelev_csetc
Implicit None
! Arguments
class(mld_s_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='s_base_onelev_csetc'
integer(psb_ipk_) :: ival
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (ival >= 0) then
call lv%set(what,ival,info,pos=pos)
else
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_s_base_onelev_csetc

@ -126,6 +126,7 @@ subroutine mld_z_base_onelev_build(lv,info,amold,vmold,imold,ilv)
lv%parms%sweeps_pre = 1 lv%parms%sweeps_pre = 1
lv%parms%sweeps_post = 1 lv%parms%sweeps_post = 1
if (me == 0) then if (me == 0) then
write(debug_unit,*)
if (present(ilv)) then if (present(ilv)) then
write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),& write(debug_unit,*) 'Warning: the solver "',trim(lv%sm%sv%get_fmt()),&
& '" at level ',ilv & '" at level ',ilv

@ -0,0 +1,286 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_csetc
use mld_z_base_aggregator_mod
use mld_z_dec_aggregator_mod
use mld_z_symdec_aggregator_mod
use mld_z_jac_smoother
use mld_z_as_smoother
use mld_z_diag_solver
use mld_z_l1_diag_solver
use mld_z_ilu_solver
use mld_z_id_solver
use mld_z_gs_solver
#if defined(HAVE_UMF_)
use mld_z_umf_solver
#endif
#if defined(HAVE_SLUDIST_)
use mld_z_sludist_solver
#endif
#if defined(HAVE_SLU_)
use mld_z_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_z_mumps_solver
#endif
Implicit None
! Arguments
class(mld_z_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='z_base_onelev_csetc'
integer(psb_ipk_) :: ival
type(mld_z_base_smoother_type) :: mld_z_base_smoother_mold
type(mld_z_jac_smoother_type) :: mld_z_jac_smoother_mold
type(mld_z_as_smoother_type) :: mld_z_as_smoother_mold
type(mld_z_diag_solver_type) :: mld_z_diag_solver_mold
type(mld_z_l1_diag_solver_type) :: mld_z_l1_diag_solver_mold
type(mld_z_ilu_solver_type) :: mld_z_ilu_solver_mold
type(mld_z_id_solver_type) :: mld_z_id_solver_mold
type(mld_z_gs_solver_type) :: mld_z_gs_solver_mold
type(mld_z_bwgs_solver_type) :: mld_z_bwgs_solver_mold
#if defined(HAVE_UMF_)
type(mld_z_umf_solver_type) :: mld_z_umf_solver_mold
#endif
#if defined(HAVE_SLUDIST_)
type(mld_z_sludist_solver_type) :: mld_z_sludist_solver_mold
#endif
#if defined(HAVE_SLU_)
type(mld_z_slu_solver_type) :: mld_z_slu_solver_mold
#endif
#if defined(HAVE_MUMPS_)
type(mld_z_mumps_solver_type) :: mld_z_mumps_solver_mold
#endif
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
select case (psb_toupper(trim(what)))
case ('SMOOTHER_TYPE')
select case (psb_toupper(trim(val)))
case ('NOPREC','NONE')
call lv%set(mld_z_base_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_z_id_solver_mold,info,pos=pos)
case ('JAC','JACOBI')
call lv%set(mld_z_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_z_diag_solver_mold,info,pos=pos)
case ('L1-JACOBI')
call lv%set(mld_z_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_z_l1_diag_solver_mold,info,pos=pos)
case ('BJAC')
call lv%set(mld_z_jac_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_z_ilu_solver_mold,info,pos=pos)
case ('AS')
call lv%set(mld_z_as_smoother_mold,info,pos=pos)
if (info == 0) call lv%set(mld_z_ilu_solver_mold,info,pos=pos)
case ('FBGS')
call lv%set(mld_z_jac_smoother_mold,info,pos='pre')
if (info == 0) call lv%set(mld_z_gs_solver_mold,info,pos='pre')
call lv%set(mld_z_jac_smoother_mold,info,pos='post')
if (info == 0) call lv%set(mld_z_bwgs_solver_mold,info,pos='post')
case default
!
! Do nothing and hope for the best :)
!
end select
if ((ipos_==mld_smooth_pre_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) call lv%sm%default()
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm2a)) call lv%sm2a%default()
end if
case('SUB_SOLVE')
select case (psb_toupper(trim(val)))
case ('NONE','NOPREC','FACT_NONE')
call lv%set(mld_z_id_solver_mold,info,pos=pos)
case ('DIAG')
call lv%set(mld_z_diag_solver_mold,info,pos=pos)
case ('L1-DIAG')
call lv%set(mld_z_l1_diag_solver_mold,info,pos=pos)
case ('GS','FGS','FWGS')
call lv%set(mld_z_gs_solver_mold,info,pos=pos)
case ('BGS','BWGS')
call lv%set(mld_z_bwgs_solver_mold,info,pos=pos)
case ('ILU','ILUT','MILU')
call lv%set(mld_z_ilu_solver_mold,info,pos=pos)
if (info == 0) then
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
call lv%sm%sv%set('SUB_SOLVE',val,info)
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) call lv%sm2a%sv%set('SUB_SOLVE',val,info)
end if
end if
#ifdef HAVE_SLU_
case ('SLU')
call lv%set(mld_z_slu_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_MUMPS_
case ('MUMPS')
call lv%set(mld_z_mumps_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_SLUDIST_
case ('SLUDIST')
call lv%set(mld_z_sludist_solver_mold,info,pos=pos)
#endif
#ifdef HAVE_UMF_
case ('UMF')
call lv%set(mld_z_umf_solver_mold,info,pos=pos)
#endif
case default
!
! Do nothing and hope for the best :)
!
end select
case ('ML_CYCLE')
lv%parms%ml_cycle = mld_stringval(val)
case ('PAR_AGGR_ALG')
ival = mld_stringval(val)
lv%parms%par_aggr_alg = ival
if (allocated(lv%aggr)) then
call lv%aggr%free(info)
if (info == 0) deallocate(lv%aggr,stat=info)
if (info /= 0) then
info = psb_err_internal_error_
return
end if
end if
select case(ival)
case(mld_dec_aggr_)
allocate(mld_z_dec_aggregator_type :: lv%aggr, stat=info)
case(mld_sym_dec_aggr_)
allocate(mld_z_symdec_aggregator_type :: lv%aggr, stat=info)
case default
info = psb_err_internal_error_
end select
if (info == psb_success_) call lv%aggr%default()
case ('AGGR_ORD')
lv%parms%aggr_ord = mld_stringval(val)
case ('AGGR_TYPE')
lv%parms%aggr_type = mld_stringval(val)
if (allocated(lv%aggr)) call lv%aggr%set_aggr_type(lv%parms,info)
case ('AGGR_PROL')
lv%parms%aggr_prol = mld_stringval(val)
case ('COARSE_MAT')
lv%parms%coarse_mat = mld_stringval(val)
case ('AGGR_OMEGA_ALG')
lv%parms%aggr_omega_alg= mld_stringval(val)
case ('AGGR_EIG')
lv%parms%aggr_eig = mld_stringval(val)
case ('AGGR_FILTER')
lv%parms%aggr_filter = mld_stringval(val)
case ('COARSE_SOLVE')
lv%parms%coarse_solve = mld_stringval(val)
case default
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_z_base_onelev_csetc

@ -1,103 +0,0 @@
!
!
! 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_base_onelev_csetc(lv,what,val,info,pos,idx)
use psb_base_mod
use mld_z_onelev_mod, mld_protect_name => mld_z_base_onelev_csetc
Implicit None
! Arguments
class(mld_z_onelev_type), intent(inout) :: lv
character(len=*), intent(in) :: what
character(len=*), intent(in) :: val
integer(psb_ipk_), intent(out) :: info
character(len=*), optional, intent(in) :: pos
integer(psb_ipk_), intent(in), optional :: idx
! Local
integer(psb_ipk_) :: ipos_, err_act
character(len=20) :: name='z_base_onelev_csetc'
integer(psb_ipk_) :: ival
call psb_erractionsave(err_act)
info = psb_success_
ival = lv%stringval(val)
if (ival >= 0) then
call lv%set(what,ival,info,pos=pos)
else
if (present(pos)) then
select case(psb_toupper(trim(pos)))
case('PRE')
ipos_ = mld_smooth_pre_
case('POST')
ipos_ = mld_smooth_post_
case default
ipos_ = mld_smooth_both_
end select
else
ipos_ = mld_smooth_both_
end if
if ((ipos_==mld_smooth_pre_) .or.(ipos_==mld_smooth_both_)) then
if (allocated(lv%sm)) then
call lv%sm%set(what,val,info,idx=idx)
end if
end if
if ((ipos_==mld_smooth_post_).or.(ipos_==mld_smooth_both_))then
if (allocated(lv%sm2a)) then
call lv%sm2a%set(what,val,info,idx=idx)
end if
end if
if (allocated(lv%aggr)) call lv%aggr%set(what,val,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act)
return
9999 call psb_error_handler(err_act)
return
end subroutine mld_z_base_onelev_csetc

@ -473,6 +473,20 @@ subroutine mld_ccprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
use psb_base_mod use psb_base_mod
use mld_c_prec_mod, mld_protect_name => mld_ccprecsetc use mld_c_prec_mod, mld_protect_name => mld_ccprecsetc
use mld_c_jac_smoother
use mld_c_as_smoother
use mld_c_diag_solver
use mld_c_l1_diag_solver
use mld_c_ilu_solver
use mld_c_id_solver
use mld_c_gs_solver
#if defined(HAVE_SLU_)
use mld_c_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_c_mumps_solver
#endif
implicit none implicit none
@ -493,15 +507,12 @@ subroutine mld_ccprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
if (.not.allocated(p%precv)) then if (.not.allocated(p%precv)) then
info = 3111 info = 3111
write(psb_err_unit,*) name,&
& ': Error: uninitialized preconditioner,',&
&' should call MLD_PRECINIT'
return return
endif endif
val = mld_stringval(string)
if (val >=0) then
call p%set(what,val,info,ilev=ilev,ilmax=ilmax,pos=pos,idx=idx)
else
nlev_ = size(p%precv) nlev_ = size(p%precv)
if (present(ilev)) then if (present(ilev)) then
@ -527,11 +538,249 @@ subroutine mld_ccprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
&': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_
return return
endif endif
!
! Set preconditioner parameters at level ilev.
!
if (present(ilev)) then
select case(psb_toupper(what))
case('SMOOTHER_TYPE','SUB_SOLVE',&
& 'ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD',&
& 'AGGR_TYPE','AGGR_PROL','AGGR_OMEGA_ALG',&
& 'AGGR_EIG','SUB_RESTR','SUB_PROL', &
& 'COARSE_MAT')
do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos)
end do
case('COARSE_SUBSOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
call p%precv(ilev_)%set('SUB_SOLVE',string,info,pos=pos)
case('COARSE_SOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (psb_toupper(trim(string)))
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','dist',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU','MILU','ILUT')
call p%precv(nlev_)%set('SMOOTHER_TYPE','bjac',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC'_,info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case default
do il=ilev_, ilmax_ do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos,idx=idx) call p%precv(il)%set(what,string,info,pos=pos,idx=idx)
end do end do
end select
else if (.not.present(ilev)) then
!
! ilev not specified: set preconditioner parameters at all the appropriate
! levels
!
select case(psb_toupper(trim(what)))
case('SUB_SOLVE','SUB_RESTR','SUB_PROL',&
& 'SMOOTHER_TYPE')
do ilev_=1,max(1,nlev_-1)
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD','AGGR_PROL','AGGR_TYPE',&
& 'AGGR_OMEGA_ALG','AGGR_EIG','AGGR_FILTER')
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('COARSE_MAT')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_MAT',string,info,pos=pos)
end if end if
case('COARSE_SOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (string)
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','DIST',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU', 'ILUT','MILU')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case('COARSE_SUBSOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
endif
case default
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos,idx=idx)
end do
end select
endif
end subroutine mld_ccprecsetc end subroutine mld_ccprecsetc

@ -507,6 +507,26 @@ subroutine mld_dcprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
use psb_base_mod use psb_base_mod
use mld_d_prec_mod, mld_protect_name => mld_dcprecsetc use mld_d_prec_mod, mld_protect_name => mld_dcprecsetc
use mld_d_jac_smoother
use mld_d_as_smoother
use mld_d_diag_solver
use mld_d_l1_diag_solver
use mld_d_ilu_solver
use mld_d_id_solver
use mld_d_gs_solver
#if defined(HAVE_UMF_)
use mld_d_umf_solver
#endif
#if defined(HAVE_SLUDIST_)
use mld_d_sludist_solver
#endif
#if defined(HAVE_SLU_)
use mld_d_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_d_mumps_solver
#endif
implicit none implicit none
@ -527,15 +547,12 @@ subroutine mld_dcprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
if (.not.allocated(p%precv)) then if (.not.allocated(p%precv)) then
info = 3111 info = 3111
write(psb_err_unit,*) name,&
& ': Error: uninitialized preconditioner,',&
&' should call MLD_PRECINIT'
return return
endif endif
val = mld_stringval(string)
if (val >=0) then
call p%set(what,val,info,ilev=ilev,ilmax=ilmax,pos=pos,idx=idx)
else
nlev_ = size(p%precv) nlev_ = size(p%precv)
if (present(ilev)) then if (present(ilev)) then
@ -561,11 +578,277 @@ subroutine mld_dcprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
&': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_
return return
endif endif
!
! Set preconditioner parameters at level ilev.
!
if (present(ilev)) then
select case(psb_toupper(what))
case('SMOOTHER_TYPE','SUB_SOLVE',&
& 'ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD',&
& 'AGGR_TYPE','AGGR_PROL','AGGR_OMEGA_ALG',&
& 'AGGR_EIG','SUB_RESTR','SUB_PROL', &
& 'COARSE_MAT')
do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos)
end do
case('COARSE_SUBSOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
call p%precv(ilev_)%set('SUB_SOLVE',string,info,pos=pos)
case('COARSE_SOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (psb_toupper(trim(string)))
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','dist',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU','MILU','ILUT')
call p%precv(nlev_)%set('SMOOTHER_TYPE','bjac',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC'_,info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLUDIST_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#elif defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case default
do il=ilev_, ilmax_ do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos,idx=idx) call p%precv(il)%set(what,string,info,pos=pos,idx=idx)
end do end do
end select
else if (.not.present(ilev)) then
!
! ilev not specified: set preconditioner parameters at all the appropriate
! levels
!
select case(psb_toupper(trim(what)))
case('SUB_SOLVE','SUB_RESTR','SUB_PROL',&
& 'SMOOTHER_TYPE')
do ilev_=1,max(1,nlev_-1)
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD','AGGR_PROL','AGGR_TYPE',&
& 'AGGR_OMEGA_ALG','AGGR_EIG','AGGR_FILTER')
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('COARSE_MAT')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_MAT',string,info,pos=pos)
end if end if
case('COARSE_SOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (string)
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','DIST',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU', 'ILUT','MILU')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLUDIST_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#elif defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case('COARSE_SUBSOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
endif
case default
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos,idx=idx)
end do
end select
endif
end subroutine mld_dcprecsetc end subroutine mld_dcprecsetc

@ -473,6 +473,20 @@ subroutine mld_scprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
use psb_base_mod use psb_base_mod
use mld_s_prec_mod, mld_protect_name => mld_scprecsetc use mld_s_prec_mod, mld_protect_name => mld_scprecsetc
use mld_s_jac_smoother
use mld_s_as_smoother
use mld_s_diag_solver
use mld_s_l1_diag_solver
use mld_s_ilu_solver
use mld_s_id_solver
use mld_s_gs_solver
#if defined(HAVE_SLU_)
use mld_s_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_s_mumps_solver
#endif
implicit none implicit none
@ -493,15 +507,12 @@ subroutine mld_scprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
if (.not.allocated(p%precv)) then if (.not.allocated(p%precv)) then
info = 3111 info = 3111
write(psb_err_unit,*) name,&
& ': Error: uninitialized preconditioner,',&
&' should call MLD_PRECINIT'
return return
endif endif
val = mld_stringval(string)
if (val >=0) then
call p%set(what,val,info,ilev=ilev,ilmax=ilmax,pos=pos,idx=idx)
else
nlev_ = size(p%precv) nlev_ = size(p%precv)
if (present(ilev)) then if (present(ilev)) then
@ -527,11 +538,249 @@ subroutine mld_scprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
&': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_
return return
endif endif
!
! Set preconditioner parameters at level ilev.
!
if (present(ilev)) then
select case(psb_toupper(what))
case('SMOOTHER_TYPE','SUB_SOLVE',&
& 'ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD',&
& 'AGGR_TYPE','AGGR_PROL','AGGR_OMEGA_ALG',&
& 'AGGR_EIG','SUB_RESTR','SUB_PROL', &
& 'COARSE_MAT')
do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos)
end do
case('COARSE_SUBSOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
call p%precv(ilev_)%set('SUB_SOLVE',string,info,pos=pos)
case('COARSE_SOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (psb_toupper(trim(string)))
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','dist',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU','MILU','ILUT')
call p%precv(nlev_)%set('SMOOTHER_TYPE','bjac',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC'_,info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case default
do il=ilev_, ilmax_ do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos,idx=idx) call p%precv(il)%set(what,string,info,pos=pos,idx=idx)
end do end do
end select
else if (.not.present(ilev)) then
!
! ilev not specified: set preconditioner parameters at all the appropriate
! levels
!
select case(psb_toupper(trim(what)))
case('SUB_SOLVE','SUB_RESTR','SUB_PROL',&
& 'SMOOTHER_TYPE')
do ilev_=1,max(1,nlev_-1)
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD','AGGR_PROL','AGGR_TYPE',&
& 'AGGR_OMEGA_ALG','AGGR_EIG','AGGR_FILTER')
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('COARSE_MAT')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_MAT',string,info,pos=pos)
end if end if
case('COARSE_SOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (string)
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','DIST',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU', 'ILUT','MILU')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case('COARSE_SUBSOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
endif
case default
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos,idx=idx)
end do
end select
endif
end subroutine mld_scprecsetc end subroutine mld_scprecsetc

@ -507,6 +507,26 @@ subroutine mld_zcprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
use psb_base_mod use psb_base_mod
use mld_z_prec_mod, mld_protect_name => mld_zcprecsetc use mld_z_prec_mod, mld_protect_name => mld_zcprecsetc
use mld_z_jac_smoother
use mld_z_as_smoother
use mld_z_diag_solver
use mld_z_l1_diag_solver
use mld_z_ilu_solver
use mld_z_id_solver
use mld_z_gs_solver
#if defined(HAVE_UMF_)
use mld_z_umf_solver
#endif
#if defined(HAVE_SLUDIST_)
use mld_z_sludist_solver
#endif
#if defined(HAVE_SLU_)
use mld_z_slu_solver
#endif
#if defined(HAVE_MUMPS_)
use mld_z_mumps_solver
#endif
implicit none implicit none
@ -527,15 +547,12 @@ subroutine mld_zcprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
if (.not.allocated(p%precv)) then if (.not.allocated(p%precv)) then
info = 3111 info = 3111
write(psb_err_unit,*) name,&
& ': Error: uninitialized preconditioner,',&
&' should call MLD_PRECINIT'
return return
endif endif
val = mld_stringval(string)
if (val >=0) then
call p%set(what,val,info,ilev=ilev,ilmax=ilmax,pos=pos,idx=idx)
else
nlev_ = size(p%precv) nlev_ = size(p%precv)
if (present(ilev)) then if (present(ilev)) then
@ -561,11 +578,277 @@ subroutine mld_zcprecsetc(p,what,string,info,ilev,ilmax,pos,idx)
&': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_ &': Error: invalid ILMAX/NLEV combination',ilmax_, nlev_
return return
endif endif
!
! Set preconditioner parameters at level ilev.
!
if (present(ilev)) then
select case(psb_toupper(what))
case('SMOOTHER_TYPE','SUB_SOLVE',&
& 'ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD',&
& 'AGGR_TYPE','AGGR_PROL','AGGR_OMEGA_ALG',&
& 'AGGR_EIG','SUB_RESTR','SUB_PROL', &
& 'COARSE_MAT')
do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos)
end do
case('COARSE_SUBSOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
call p%precv(ilev_)%set('SUB_SOLVE',string,info,pos=pos)
case('COARSE_SOLVE')
if (ilev_ /= nlev_) then
write(psb_err_unit,*) name,&
& ': Error: Inconsistent specification of WHAT vs. ILEV'
info = -2
return
end if
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (psb_toupper(trim(string)))
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','dist',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU','MILU','ILUT')
call p%precv(nlev_)%set('SMOOTHER_TYPE','bjac',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC'_,info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLUDIST_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#elif defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case default
do il=ilev_, ilmax_ do il=ilev_, ilmax_
call p%precv(il)%set(what,string,info,pos=pos,idx=idx) call p%precv(il)%set(what,string,info,pos=pos,idx=idx)
end do end do
end select
else if (.not.present(ilev)) then
!
! ilev not specified: set preconditioner parameters at all the appropriate
! levels
!
select case(psb_toupper(trim(what)))
case('SUB_SOLVE','SUB_RESTR','SUB_PROL',&
& 'SMOOTHER_TYPE')
do ilev_=1,max(1,nlev_-1)
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('ML_CYCLE','PAR_AGGR_ALG','AGGR_ORD','AGGR_PROL','AGGR_TYPE',&
& 'AGGR_OMEGA_ALG','AGGR_EIG','AGGR_FILTER')
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos)
if (info /= 0) return
end do
case('COARSE_MAT')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_MAT',string,info,pos=pos)
end if end if
case('COARSE_SOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('COARSE_SOLVE',string,info,pos=pos)
select case (string)
case('BJAC')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
#else
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
#endif
call p%precv(nlev_)%set('COARSE_MAT','DIST',info)
case('SLU')
#if defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('ILU', 'ILUT','MILU')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
case('MUMPS')
#if defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('UMF')
#if defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('SLUDIST')
#if defined(HAVE_SLUDIST_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#elif defined(HAVE_UMF_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','UMF',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_SLU_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','SLU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','REPL',info,pos=pos)
#elif defined(HAVE_MUMPS_)
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','MUMPS',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#else
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','ILU',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
#endif
case('JAC','JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
case('L1-JACOBI')
call p%precv(nlev_)%set('SMOOTHER_TYPE','BJAC',info,pos=pos)
call p%precv(nlev_)%set('SUB_SOLVE','L1-DIAG',info,pos=pos)
call p%precv(nlev_)%set('COARSE_MAT','DIST',info,pos=pos)
end select
endif
case('COARSE_SUBSOLVE')
if (nlev_ > 1) then
call p%precv(nlev_)%set('SUB_SOLVE',string,info,pos=pos)
endif
case default
do ilev_=1,nlev_
call p%precv(ilev_)%set(what,string,info,pos=pos,idx=idx)
end do
end select
endif
end subroutine mld_zcprecsetc end subroutine mld_zcprecsetc

@ -54,11 +54,14 @@ subroutine mld_c_as_smoother_csetc(sm,what,val,info,idx)
ival = sm%stringval(val) ival = sm%stringval(val)
if (ival >= 0) then select case(psb_toupper(what))
call sm%set(what,ival,info,idx=idx) case('SUB_RESTR')
else sm%restr = ival
case('SUB_PROL')
sm%prol = ival
case default
call sm%mld_c_base_smoother_type%set(what,val,info,idx=idx) call sm%mld_c_base_smoother_type%set(what,val,info,idx=idx)
end if end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -54,14 +54,9 @@ subroutine mld_c_base_smoother_csetc(sm,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sm%stringval(val)
if (ival >= 0) then
call sm%set(what,ival,info,idx=idx)
else
if (allocated(sm%sv)) then if (allocated(sm%sv)) then
call sm%sv%set(what,val,info,idx=idx) call sm%sv%set(what,val,info,idx=idx)
end if end if
end if
if (info /= psb_success_) goto 9999 if (info /= psb_success_) goto 9999

@ -54,11 +54,14 @@ subroutine mld_d_as_smoother_csetc(sm,what,val,info,idx)
ival = sm%stringval(val) ival = sm%stringval(val)
if (ival >= 0) then select case(psb_toupper(what))
call sm%set(what,ival,info,idx=idx) case('SUB_RESTR')
else sm%restr = ival
case('SUB_PROL')
sm%prol = ival
case default
call sm%mld_d_base_smoother_type%set(what,val,info,idx=idx) call sm%mld_d_base_smoother_type%set(what,val,info,idx=idx)
end if end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -54,14 +54,9 @@ subroutine mld_d_base_smoother_csetc(sm,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sm%stringval(val)
if (ival >= 0) then
call sm%set(what,ival,info,idx=idx)
else
if (allocated(sm%sv)) then if (allocated(sm%sv)) then
call sm%sv%set(what,val,info,idx=idx) call sm%sv%set(what,val,info,idx=idx)
end if end if
end if
if (info /= psb_success_) goto 9999 if (info /= psb_success_) goto 9999

@ -54,11 +54,14 @@ subroutine mld_s_as_smoother_csetc(sm,what,val,info,idx)
ival = sm%stringval(val) ival = sm%stringval(val)
if (ival >= 0) then select case(psb_toupper(what))
call sm%set(what,ival,info,idx=idx) case('SUB_RESTR')
else sm%restr = ival
case('SUB_PROL')
sm%prol = ival
case default
call sm%mld_s_base_smoother_type%set(what,val,info,idx=idx) call sm%mld_s_base_smoother_type%set(what,val,info,idx=idx)
end if end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -54,14 +54,9 @@ subroutine mld_s_base_smoother_csetc(sm,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sm%stringval(val)
if (ival >= 0) then
call sm%set(what,ival,info,idx=idx)
else
if (allocated(sm%sv)) then if (allocated(sm%sv)) then
call sm%sv%set(what,val,info,idx=idx) call sm%sv%set(what,val,info,idx=idx)
end if end if
end if
if (info /= psb_success_) goto 9999 if (info /= psb_success_) goto 9999

@ -54,11 +54,14 @@ subroutine mld_z_as_smoother_csetc(sm,what,val,info,idx)
ival = sm%stringval(val) ival = sm%stringval(val)
if (ival >= 0) then select case(psb_toupper(what))
call sm%set(what,ival,info,idx=idx) case('SUB_RESTR')
else sm%restr = ival
case('SUB_PROL')
sm%prol = ival
case default
call sm%mld_z_base_smoother_type%set(what,val,info,idx=idx) call sm%mld_z_base_smoother_type%set(what,val,info,idx=idx)
end if end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -54,14 +54,9 @@ subroutine mld_z_base_smoother_csetc(sm,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sm%stringval(val)
if (ival >= 0) then
call sm%set(what,ival,info,idx=idx)
else
if (allocated(sm%sv)) then if (allocated(sm%sv)) then
call sm%sv%set(what,val,info,idx=idx) call sm%sv%set(what,val,info,idx=idx)
end if end if
end if
if (info /= psb_success_) goto 9999 if (info /= psb_success_) goto 9999

@ -53,13 +53,6 @@ subroutine mld_c_base_solver_csetc(sv,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sv%stringval(val)
if (ival >=0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -53,13 +53,6 @@ subroutine mld_d_base_solver_csetc(sv,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sv%stringval(val)
if (ival >=0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -53,13 +53,6 @@ subroutine mld_s_base_solver_csetc(sv,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sv%stringval(val)
if (ival >=0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -53,13 +53,6 @@ subroutine mld_z_base_solver_csetc(sv,what,val,info,idx)
info = psb_success_ info = psb_success_
ival = sv%stringval(val)
if (ival >=0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) goto 9999
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -335,10 +335,7 @@ contains
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = sv%stringval(val) call sv%mld_c_base_solver_type%set(what,val,info,idx=idx)
if (ival >= 0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -263,7 +263,7 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
select case(psb_toupper(what)) select case(psb_toupper(trim((what))))
case('SUB_SOLVE') case('SUB_SOLVE')
sv%fact_type = val sv%fact_type = val
case('SUB_FILLIN') case('SUB_FILLIN')
@ -294,12 +294,13 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = mld_stringval(val)
select case(psb_toupper(trim((what))))
ival = sv%stringval(val) case('SUB_SOLVE')
if (ival >= 0) then sv%fact_type = ival
call sv%set(what,ival,info,idx=idx) case default
end if call sv%mld_c_base_solver_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -335,10 +335,7 @@ contains
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = sv%stringval(val) call sv%mld_d_base_solver_type%set(what,val,info,idx=idx)
if (ival >= 0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -263,7 +263,7 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
select case(psb_toupper(what)) select case(psb_toupper(trim((what))))
case('SUB_SOLVE') case('SUB_SOLVE')
sv%fact_type = val sv%fact_type = val
case('SUB_FILLIN') case('SUB_FILLIN')
@ -294,12 +294,13 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = mld_stringval(val)
select case(psb_toupper(trim((what))))
ival = sv%stringval(val) case('SUB_SOLVE')
if (ival >= 0) then sv%fact_type = ival
call sv%set(what,ival,info,idx=idx) case default
end if call sv%mld_d_base_solver_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -335,10 +335,7 @@ contains
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = sv%stringval(val) call sv%mld_s_base_solver_type%set(what,val,info,idx=idx)
if (ival >= 0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -263,7 +263,7 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
select case(psb_toupper(what)) select case(psb_toupper(trim((what))))
case('SUB_SOLVE') case('SUB_SOLVE')
sv%fact_type = val sv%fact_type = val
case('SUB_FILLIN') case('SUB_FILLIN')
@ -294,12 +294,13 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = mld_stringval(val)
select case(psb_toupper(trim((what))))
ival = sv%stringval(val) case('SUB_SOLVE')
if (ival >= 0) then sv%fact_type = ival
call sv%set(what,ival,info,idx=idx) case default
end if call sv%mld_s_base_solver_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -335,10 +335,7 @@ contains
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = sv%stringval(val) call sv%mld_z_base_solver_type%set(what,val,info,idx=idx)
if (ival >= 0) then
call sv%set(what,ival,info,idx=idx)
end if
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

@ -263,7 +263,7 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
select case(psb_toupper(what)) select case(psb_toupper(trim((what))))
case('SUB_SOLVE') case('SUB_SOLVE')
sv%fact_type = val sv%fact_type = val
case('SUB_FILLIN') case('SUB_FILLIN')
@ -294,12 +294,13 @@ contains
info = psb_success_ info = psb_success_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
ival = mld_stringval(val)
select case(psb_toupper(trim((what))))
ival = sv%stringval(val) case('SUB_SOLVE')
if (ival >= 0) then sv%fact_type = ival
call sv%set(what,ival,info,idx=idx) case default
end if call sv%mld_z_base_solver_type%set(what,val,info,idx=idx)
end select
if (info /= psb_success_) then if (info /= psb_success_) then
info = psb_err_from_subroutine_ info = psb_err_from_subroutine_

Loading…
Cancel
Save