$ case('2LDI4') $ call prec%init('ml',info,nlev=2) $ call prec%set(sub_restr_,psb_halo_,info) $ call prec%set(coarse_solve_,ilu_n_,info) $ call prec%set(coarse_sweeps_,4,info) $ case('2LDU4') $ call prec%init('ml',info,nlev=2) $ call prec%set(sub_restr_,psb_halo_,info) $ call prec%set(coarse_solve_,umf_,info) $ call prec%set(coarse_sweeps_,4,info) $ case('3LDI4') $ call prec%init('ml',info,nlev=3) $ call prec%set(sub_restr_,psb_halo_,info) $ call prec%set(coarse_solve_,ilu_n_,info) $ call prec%set(coarse_sweeps_,4,info) $ case('3LDU4') $ call prec%init('ml',info,nlev=3) $ call prec%set(sub_restr_,psb_halo_,info) $ call prec%set(coarse_solve_,umf_,info) $ call prec%set(coarse_sweeps_,4,info) $ case('2LI4S') $ call prec%init('ml',info,nlev=2) $ call prec%set(coarse_solve_,ilu_n_,info) $ call prec%set(coarse_sweeps_,4,info) $ case('2LU4S') $ call prec%init('ml',info,nlev=2) $ call prec%set(coarse_solve_,umf_,info) $ call prec%set(coarse_sweeps_,4,info) $ case('3LI4S') $ call prec%init('ml',info,nlev=3) $ call prec%set(coarse_solve_,ilu_n_,info) $ call prec%set(coarse_sweeps_,4,info) $ case('3LU4S') $ call prec%init('ml',info,nlev=3) $ call prec%set(coarse_solve_,umf_,info) $ call prec%set(coarse_sweeps_,4,info) $ ! RAS and Multilevel preconditioners requires BICGSTAB. $ if( cprec == 'RASI' .or. & $ & cprec == 'NLDI' .or. & $ & cprec == 'NLDU') then $ if(cmethod /= 'BICGSTAB') then $ write(*,300) $ call abort_psblas $ end if $ end if
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=*), | intent(in) | :: | cprec | |||
integer, | intent(in) | :: | nlev | |||
character(len=*), | intent(in) | :: | cmethod | |||
type(psb_dspmat_type), | intent(in) | :: | a | |||
type(psb_desc_type), | intent(inout) | :: | desc_a | |||
type(psb_dprec_type), | intent(inout) | :: | prec |
SUBROUTINE psb_build_prec(cprec,nlev,cmethod,A,desc_a,prec)
USE class_psblas
USE psb_base_mod
USE psb_prec_mod
IMPLICIT NONE
CHARACTER(len=*), INTENT(IN) :: cprec
INTEGER, INTENT(IN) :: nlev
CHARACTER(len=*), INTENT(IN) :: cmethod
TYPE(psb_dspmat_type), INTENT(IN) :: A
TYPE(psb_desc_type), INTENT(INOUT) :: desc_a
TYPE(psb_dprec_type), INTENT(INOUT) :: prec
!
INTEGER(psb_ipk_) :: info
INTEGER :: err_act
INTEGER :: icontxt, mypnum
INTEGER :: nlev_
! Sets error handling for PSBLAS-2 routines
info = 0
CALL psb_erractionsave(err_act)
! Temporary dummy argument
nlev_ = nlev
icontxt = icontxt_()
mypnum = mypnum_()
CALL sw_pre%tic()
! Prepares the preconditioner
SELECT CASE(psb_toupper(TRIM(cprec)))
CASE('NOPREC','NONE','DIAG','BJAC')
! These are OK.
CALL prec%init(TRIM(cprec),info)
!!$ case('2LDI4')
!!$ call prec%init('ml',info,nlev=2)
!!$ call prec%set(sub_restr_,psb_halo_,info)
!!$ call prec%set(coarse_solve_,ilu_n_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
!!$ case('2LDU4')
!!$ call prec%init('ml',info,nlev=2)
!!$ call prec%set(sub_restr_,psb_halo_,info)
!!$ call prec%set(coarse_solve_,umf_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
!!$ case('3LDI4')
!!$ call prec%init('ml',info,nlev=3)
!!$ call prec%set(sub_restr_,psb_halo_,info)
!!$ call prec%set(coarse_solve_,ilu_n_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
!!$ case('3LDU4')
!!$ call prec%init('ml',info,nlev=3)
!!$ call prec%set(sub_restr_,psb_halo_,info)
!!$ call prec%set(coarse_solve_,umf_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
!!$ case('2LI4S')
!!$ call prec%init('ml',info,nlev=2)
!!$ call prec%set(coarse_solve_,ilu_n_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
!!$ case('2LU4S')
!!$ call prec%init('ml',info,nlev=2)
!!$ call prec%set(coarse_solve_,umf_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
!!$ case('3LI4S')
!!$ call prec%init('ml',info,nlev=3)
!!$ call prec%set(coarse_solve_,ilu_n_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
!!$ case('3LU4S')
!!$ call prec%init('ml',info,nlev=3)
!!$ call prec%set(coarse_solve_,umf_,info)
!!$ call prec%set(coarse_sweeps_,4,info)
CASE DEFAULT
WRITE(*,100)
CALL abort_psblas
END SELECT
CALL psb_check_error(info,'psb_build_prec','psb_precinit',icontxt)
! Checks preconditioner compatibility with CG method.
IF(psb_toupper(cmethod) == 'CG') THEN
SELECT CASE(psb_toupper(TRIM(cprec)))
CASE ('NOPREC','DIAG','BJAC','2LI4S','2LU4S','3LI4S','3LU4S')
! Things are OK
CASE DEFAULT
WRITE(*,200)
CALL abort_psblas
END SELECT
END IF
!!$ ! RAS and Multilevel preconditioners requires BICGSTAB.
!!$ if( cprec == 'RASI' .or. &
!!$ & cprec == 'NLDI' .or. &
!!$ & cprec == 'NLDU') then
!!$ if(cmethod /= 'BICGSTAB') then
!!$ write(*,300)
!!$ call abort_psblas
!!$ end if
!!$ end if
! Builds preconditioner
IF(mypnum == 0) THEN
WRITE(*,*) ' + Setting preconditioner to: ',TRIM(cprec)
END IF
CALL prec%build(A,desc_a,info)
CALL psb_check_error(info,'psb_build_prec','psb_precbld',icontxt)
! ----- Normal Termination -----
CALL psb_erractionrestore(err_act)
CALL sw_pre%toc()
100 FORMAT(' ERROR! Unsupported preconditioner in PSB_BUILD_PREC')
200 FORMAT(' ERROR! Unsymmetric preconditioner cannot be used with CG')
300 FORMAT(' ERROR! RAS(ML) preconditioners need BICGSTAB')
END SUBROUTINE psb_build_prec