Change interface to descr with verbosity level

newG2L
Salvatore Filippone 4 years ago
parent 583ca19e9c
commit 0bcc32c626

@ -161,7 +161,7 @@ module psb_c_base_prec_mod
abstract interface abstract interface
subroutine psb_c_base_precdescr(prec,iout,root) subroutine psb_c_base_precdescr(prec,iout,root, verbosity)
import psb_ipk_, psb_spk_, psb_desc_type, psb_c_vect_type, & import psb_ipk_, psb_spk_, psb_desc_type, psb_c_vect_type, &
& psb_c_base_vect_type, psb_cspmat_type, psb_c_base_prec_type,& & psb_c_base_vect_type, psb_cspmat_type, psb_c_base_prec_type,&
& psb_c_base_sparse_mat & psb_c_base_sparse_mat
@ -170,6 +170,7 @@ module psb_c_base_prec_mod
class(psb_c_base_prec_type), intent(in) :: prec class(psb_c_base_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
end subroutine psb_c_base_precdescr end subroutine psb_c_base_precdescr
end interface end interface

@ -151,7 +151,14 @@ module psb_c_bjacprec
contains contains
subroutine psb_c_bjac_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_c_bjac_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
implicit none implicit none
@ -159,11 +166,12 @@ contains
class(psb_c_bjac_prec_type), intent(in) :: prec class(psb_c_bjac_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='c_bjac_precdescr' character(len=20) :: name='c_bjac_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -180,6 +188,13 @@ contains
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (.not.allocated(prec%iprcparm)) then if (.not.allocated(prec%iprcparm)) then
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
@ -195,6 +210,7 @@ contains
& 'Block Jacobi with: ',& & 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_)) & fact_names(prec%iprcparm(psb_f_type_))
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -160,7 +160,14 @@ contains
end subroutine psb_c_diag_precfree end subroutine psb_c_diag_precfree
subroutine psb_c_diag_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_c_diag_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
Implicit None Implicit None
@ -168,11 +175,12 @@ contains
class(psb_c_diag_prec_type), intent(in) :: prec class(psb_c_diag_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='c_diag_precdescr' character(len=20) :: name='c_diag_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -188,6 +196,12 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
@ -202,6 +216,7 @@ contains
info = psb_success_ info = psb_success_
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -156,7 +156,14 @@ contains
end subroutine psb_c_null_precfree end subroutine psb_c_null_precfree
subroutine psb_c_null_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_c_null_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
@ -165,13 +172,14 @@ contains
class(psb_c_null_prec_type), intent(in) :: prec class(psb_c_null_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='c_null_precset' character(len=20) :: name='c_null_precset'
character(len=32) :: dprefix, frmtv character(len=32) :: dprefix, frmtv
integer(psb_ipk_) :: ni integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -187,16 +195,22 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
if (root_ == -1) root_ = iam if (root_ == -1) root_ = iam
if (iam == root_) & if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',& & write(iout_,*) trim(prec%desc_prefix()),' ',&
& 'No preconditioning' & 'No preconditioning'
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -190,13 +190,22 @@ end interface
contains contains
subroutine psb_cfile_prec_descr(prec,iout, root) !
!
! verbosity:
! -1: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_cfile_prec_descr(prec,iout, root,verbosity)
use psb_base_mod use psb_base_mod
implicit none implicit none
class(psb_cprec_type), intent(in) :: prec class(psb_cprec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_) :: iout_,info integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: iout_,info, verbosity_
character(len=20) :: name='prec_descr' character(len=20) :: name='prec_descr'
if (present(iout)) then if (present(iout)) then
@ -209,7 +218,7 @@ contains
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
end if end if
call prec%prec%descr(iout=iout,root=root) call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
end subroutine psb_cfile_prec_descr end subroutine psb_cfile_prec_descr

@ -161,7 +161,7 @@ module psb_d_base_prec_mod
abstract interface abstract interface
subroutine psb_d_base_precdescr(prec,iout,root) subroutine psb_d_base_precdescr(prec,iout,root, verbosity)
import psb_ipk_, psb_dpk_, psb_desc_type, psb_d_vect_type, & import psb_ipk_, psb_dpk_, psb_desc_type, psb_d_vect_type, &
& psb_d_base_vect_type, psb_dspmat_type, psb_d_base_prec_type,& & psb_d_base_vect_type, psb_dspmat_type, psb_d_base_prec_type,&
& psb_d_base_sparse_mat & psb_d_base_sparse_mat
@ -170,6 +170,7 @@ module psb_d_base_prec_mod
class(psb_d_base_prec_type), intent(in) :: prec class(psb_d_base_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
end subroutine psb_d_base_precdescr end subroutine psb_d_base_precdescr
end interface end interface

@ -151,7 +151,14 @@ module psb_d_bjacprec
contains contains
subroutine psb_d_bjac_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_d_bjac_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
implicit none implicit none
@ -159,11 +166,12 @@ contains
class(psb_d_bjac_prec_type), intent(in) :: prec class(psb_d_bjac_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='d_bjac_precdescr' character(len=20) :: name='d_bjac_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -180,6 +188,13 @@ contains
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (.not.allocated(prec%iprcparm)) then if (.not.allocated(prec%iprcparm)) then
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
@ -195,6 +210,7 @@ contains
& 'Block Jacobi with: ',& & 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_)) & fact_names(prec%iprcparm(psb_f_type_))
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -160,7 +160,14 @@ contains
end subroutine psb_d_diag_precfree end subroutine psb_d_diag_precfree
subroutine psb_d_diag_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_d_diag_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
Implicit None Implicit None
@ -168,11 +175,12 @@ contains
class(psb_d_diag_prec_type), intent(in) :: prec class(psb_d_diag_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='d_diag_precdescr' character(len=20) :: name='d_diag_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -188,6 +196,12 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
@ -202,6 +216,7 @@ contains
info = psb_success_ info = psb_success_
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -156,7 +156,14 @@ contains
end subroutine psb_d_null_precfree end subroutine psb_d_null_precfree
subroutine psb_d_null_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_d_null_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
@ -165,13 +172,14 @@ contains
class(psb_d_null_prec_type), intent(in) :: prec class(psb_d_null_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='d_null_precset' character(len=20) :: name='d_null_precset'
character(len=32) :: dprefix, frmtv character(len=32) :: dprefix, frmtv
integer(psb_ipk_) :: ni integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -187,16 +195,22 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
if (root_ == -1) root_ = iam if (root_ == -1) root_ = iam
if (iam == root_) & if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',& & write(iout_,*) trim(prec%desc_prefix()),' ',&
& 'No preconditioning' & 'No preconditioning'
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -190,13 +190,22 @@ end interface
contains contains
subroutine psb_dfile_prec_descr(prec,iout, root) !
!
! verbosity:
! -1: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_dfile_prec_descr(prec,iout, root,verbosity)
use psb_base_mod use psb_base_mod
implicit none implicit none
class(psb_dprec_type), intent(in) :: prec class(psb_dprec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_) :: iout_,info integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: iout_,info, verbosity_
character(len=20) :: name='prec_descr' character(len=20) :: name='prec_descr'
if (present(iout)) then if (present(iout)) then
@ -209,7 +218,7 @@ contains
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
end if end if
call prec%prec%descr(iout=iout,root=root) call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
end subroutine psb_dfile_prec_descr end subroutine psb_dfile_prec_descr

@ -161,7 +161,7 @@ module psb_s_base_prec_mod
abstract interface abstract interface
subroutine psb_s_base_precdescr(prec,iout,root) subroutine psb_s_base_precdescr(prec,iout,root, verbosity)
import psb_ipk_, psb_spk_, psb_desc_type, psb_s_vect_type, & import psb_ipk_, psb_spk_, psb_desc_type, psb_s_vect_type, &
& psb_s_base_vect_type, psb_sspmat_type, psb_s_base_prec_type,& & psb_s_base_vect_type, psb_sspmat_type, psb_s_base_prec_type,&
& psb_s_base_sparse_mat & psb_s_base_sparse_mat
@ -170,6 +170,7 @@ module psb_s_base_prec_mod
class(psb_s_base_prec_type), intent(in) :: prec class(psb_s_base_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
end subroutine psb_s_base_precdescr end subroutine psb_s_base_precdescr
end interface end interface

@ -151,7 +151,14 @@ module psb_s_bjacprec
contains contains
subroutine psb_s_bjac_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_s_bjac_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
implicit none implicit none
@ -159,11 +166,12 @@ contains
class(psb_s_bjac_prec_type), intent(in) :: prec class(psb_s_bjac_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='s_bjac_precdescr' character(len=20) :: name='s_bjac_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -180,6 +188,13 @@ contains
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (.not.allocated(prec%iprcparm)) then if (.not.allocated(prec%iprcparm)) then
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
@ -195,6 +210,7 @@ contains
& 'Block Jacobi with: ',& & 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_)) & fact_names(prec%iprcparm(psb_f_type_))
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -160,7 +160,14 @@ contains
end subroutine psb_s_diag_precfree end subroutine psb_s_diag_precfree
subroutine psb_s_diag_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_s_diag_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
Implicit None Implicit None
@ -168,11 +175,12 @@ contains
class(psb_s_diag_prec_type), intent(in) :: prec class(psb_s_diag_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='s_diag_precdescr' character(len=20) :: name='s_diag_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -188,6 +196,12 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
@ -202,6 +216,7 @@ contains
info = psb_success_ info = psb_success_
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -156,7 +156,14 @@ contains
end subroutine psb_s_null_precfree end subroutine psb_s_null_precfree
subroutine psb_s_null_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_s_null_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
@ -165,13 +172,14 @@ contains
class(psb_s_null_prec_type), intent(in) :: prec class(psb_s_null_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='s_null_precset' character(len=20) :: name='s_null_precset'
character(len=32) :: dprefix, frmtv character(len=32) :: dprefix, frmtv
integer(psb_ipk_) :: ni integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -187,16 +195,22 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
if (root_ == -1) root_ = iam if (root_ == -1) root_ = iam
if (iam == root_) & if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',& & write(iout_,*) trim(prec%desc_prefix()),' ',&
& 'No preconditioning' & 'No preconditioning'
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -190,13 +190,22 @@ end interface
contains contains
subroutine psb_sfile_prec_descr(prec,iout, root) !
!
! verbosity:
! -1: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_sfile_prec_descr(prec,iout, root,verbosity)
use psb_base_mod use psb_base_mod
implicit none implicit none
class(psb_sprec_type), intent(in) :: prec class(psb_sprec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_) :: iout_,info integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: iout_,info, verbosity_
character(len=20) :: name='prec_descr' character(len=20) :: name='prec_descr'
if (present(iout)) then if (present(iout)) then
@ -209,7 +218,7 @@ contains
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
end if end if
call prec%prec%descr(iout=iout,root=root) call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
end subroutine psb_sfile_prec_descr end subroutine psb_sfile_prec_descr

@ -161,7 +161,7 @@ module psb_z_base_prec_mod
abstract interface abstract interface
subroutine psb_z_base_precdescr(prec,iout,root) subroutine psb_z_base_precdescr(prec,iout,root, verbosity)
import psb_ipk_, psb_dpk_, psb_desc_type, psb_z_vect_type, & import psb_ipk_, psb_dpk_, psb_desc_type, psb_z_vect_type, &
& psb_z_base_vect_type, psb_zspmat_type, psb_z_base_prec_type,& & psb_z_base_vect_type, psb_zspmat_type, psb_z_base_prec_type,&
& psb_z_base_sparse_mat & psb_z_base_sparse_mat
@ -170,6 +170,7 @@ module psb_z_base_prec_mod
class(psb_z_base_prec_type), intent(in) :: prec class(psb_z_base_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
end subroutine psb_z_base_precdescr end subroutine psb_z_base_precdescr
end interface end interface

@ -151,7 +151,14 @@ module psb_z_bjacprec
contains contains
subroutine psb_z_bjac_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_z_bjac_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
implicit none implicit none
@ -159,11 +166,12 @@ contains
class(psb_z_bjac_prec_type), intent(in) :: prec class(psb_z_bjac_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='z_bjac_precdescr' character(len=20) :: name='z_bjac_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -180,6 +188,13 @@ contains
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (.not.allocated(prec%iprcparm)) then if (.not.allocated(prec%iprcparm)) then
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
@ -195,6 +210,7 @@ contains
& 'Block Jacobi with: ',& & 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_)) & fact_names(prec%iprcparm(psb_f_type_))
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -160,7 +160,14 @@ contains
end subroutine psb_z_diag_precfree end subroutine psb_z_diag_precfree
subroutine psb_z_diag_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_z_diag_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
Implicit None Implicit None
@ -168,11 +175,12 @@ contains
class(psb_z_diag_prec_type), intent(in) :: prec class(psb_z_diag_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='z_diag_precdescr' character(len=20) :: name='z_diag_precdescr'
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -188,6 +196,12 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
@ -202,6 +216,7 @@ contains
info = psb_success_ info = psb_success_
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -156,7 +156,14 @@ contains
end subroutine psb_z_null_precfree end subroutine psb_z_null_precfree
subroutine psb_z_null_precdescr(prec,iout,root) !
!
! verbosity:
! <0: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_z_null_precdescr(prec,iout,root, verbosity)
use psb_penv_mod use psb_penv_mod
use psb_error_mod use psb_error_mod
@ -165,13 +172,14 @@ contains
class(psb_z_null_prec_type), intent(in) :: prec class(psb_z_null_prec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: err_act, nrow, info integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='z_null_precset' character(len=20) :: name='z_null_precset'
character(len=32) :: dprefix, frmtv character(len=32) :: dprefix, frmtv
integer(psb_ipk_) :: ni integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_ integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -187,16 +195,22 @@ contains
else else
root_ = psb_root_ root_ = psb_root_
end if end if
if (present(verbosity)) then
verbosity_ = verbosity
else
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt ctxt = prec%ctxt
call psb_info(ctxt,iam,np) call psb_info(ctxt,iam,np)
if (root_ == -1) root_ = iam if (root_ == -1) root_ = iam
if (iam == root_) & if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',& & write(iout_,*) trim(prec%desc_prefix()),' ',&
& 'No preconditioning' & 'No preconditioning'
9998 continue
call psb_erractionrestore(err_act) call psb_erractionrestore(err_act)
return return

@ -190,13 +190,22 @@ end interface
contains contains
subroutine psb_zfile_prec_descr(prec,iout, root) !
!
! verbosity:
! -1: suppress all messages
! 0: normal
! >1: increased details
!
subroutine psb_zfile_prec_descr(prec,iout, root,verbosity)
use psb_base_mod use psb_base_mod
implicit none implicit none
class(psb_zprec_type), intent(in) :: prec class(psb_zprec_type), intent(in) :: prec
integer(psb_ipk_), intent(in), optional :: iout integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_) :: iout_,info integer(psb_ipk_), intent(in), optional :: verbosity
integer(psb_ipk_) :: iout_,info, verbosity_
character(len=20) :: name='prec_descr' character(len=20) :: name='prec_descr'
if (present(iout)) then if (present(iout)) then
@ -209,7 +218,7 @@ contains
info = 1124 info = 1124
call psb_errpush(info,name,a_err="preconditioner") call psb_errpush(info,name,a_err="preconditioner")
end if end if
call prec%prec%descr(iout=iout,root=root) call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
end subroutine psb_zfile_prec_descr end subroutine psb_zfile_prec_descr

Loading…
Cancel
Save