Fix PREFIX in PREC%DESCR

tspmm
Salvatore Filippone 3 years ago
parent 12277b0163
commit 7fe4828099

@ -161,17 +161,17 @@ module psb_c_base_prec_mod
abstract interface
subroutine psb_c_base_precdescr(prec,iout,root, verbosity)
subroutine psb_c_base_precdescr(prec,iout,root, verbosity,prefix)
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_sparse_mat
Implicit None
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 :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
end subroutine psb_c_base_precdescr
end interface

@ -158,7 +158,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_c_bjac_precdescr(prec,iout,root, verbosity)
subroutine psb_c_bjac_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
implicit none
@ -167,11 +167,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='c_bjac_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -194,6 +196,11 @@ contains
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (.not.allocated(prec%iprcparm)) then
info = 1124
@ -206,7 +213,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_))

@ -167,7 +167,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_c_diag_precdescr(prec,iout,root, verbosity)
subroutine psb_c_diag_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
Implicit None
@ -176,11 +176,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='c_diag_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -201,6 +203,11 @@ contains
else
verbosity_ = 0
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt
@ -209,7 +216,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Diagonal scaling'
call psb_erractionsave(err_act)

@ -163,7 +163,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_c_null_precdescr(prec,iout,root, verbosity)
subroutine psb_c_null_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
@ -173,6 +173,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='c_null_precset'
@ -180,6 +181,7 @@ contains
integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -195,6 +197,11 @@ contains
else
root_ = psb_root_
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (present(verbosity)) then
verbosity_ = verbosity
else
@ -207,7 +214,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'No preconditioning'
9998 continue

@ -197,7 +197,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_cfile_prec_descr(prec,info,iout, root,verbosity)
subroutine psb_cfile_prec_descr(prec,info,iout, root,verbosity,prefix)
use psb_base_mod
implicit none
class(psb_cprec_type), intent(in) :: prec
@ -205,6 +205,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: iout_, verbosity_
character(len=20) :: name='prec_descr'
@ -219,7 +220,7 @@ contains
info = 1124
call psb_errpush(info,name,a_err="preconditioner")
end if
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity,prefix=prefix)
end subroutine psb_cfile_prec_descr

@ -161,17 +161,17 @@ module psb_d_base_prec_mod
abstract interface
subroutine psb_d_base_precdescr(prec,iout,root, verbosity)
subroutine psb_d_base_precdescr(prec,iout,root, verbosity,prefix)
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_sparse_mat
Implicit None
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 :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
end subroutine psb_d_base_precdescr
end interface

@ -158,7 +158,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_d_bjac_precdescr(prec,iout,root, verbosity)
subroutine psb_d_bjac_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
implicit none
@ -167,11 +167,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='d_bjac_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -194,6 +196,11 @@ contains
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (.not.allocated(prec%iprcparm)) then
info = 1124
@ -206,7 +213,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_))

@ -167,7 +167,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_d_diag_precdescr(prec,iout,root, verbosity)
subroutine psb_d_diag_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
Implicit None
@ -176,11 +176,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='d_diag_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -201,6 +203,11 @@ contains
else
verbosity_ = 0
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt
@ -209,7 +216,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Diagonal scaling'
call psb_erractionsave(err_act)

@ -163,7 +163,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_d_null_precdescr(prec,iout,root, verbosity)
subroutine psb_d_null_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
@ -173,6 +173,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='d_null_precset'
@ -180,6 +181,7 @@ contains
integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -195,6 +197,11 @@ contains
else
root_ = psb_root_
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (present(verbosity)) then
verbosity_ = verbosity
else
@ -207,7 +214,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'No preconditioning'
9998 continue

@ -197,7 +197,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_dfile_prec_descr(prec,info,iout, root,verbosity)
subroutine psb_dfile_prec_descr(prec,info,iout, root,verbosity,prefix)
use psb_base_mod
implicit none
class(psb_dprec_type), intent(in) :: prec
@ -205,6 +205,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: iout_, verbosity_
character(len=20) :: name='prec_descr'
@ -219,7 +220,7 @@ contains
info = 1124
call psb_errpush(info,name,a_err="preconditioner")
end if
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity,prefix=prefix)
end subroutine psb_dfile_prec_descr

@ -161,17 +161,17 @@ module psb_s_base_prec_mod
abstract interface
subroutine psb_s_base_precdescr(prec,iout,root, verbosity)
subroutine psb_s_base_precdescr(prec,iout,root, verbosity,prefix)
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_sparse_mat
Implicit None
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 :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
end subroutine psb_s_base_precdescr
end interface

@ -158,7 +158,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_s_bjac_precdescr(prec,iout,root, verbosity)
subroutine psb_s_bjac_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
implicit none
@ -167,11 +167,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='s_bjac_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -194,6 +196,11 @@ contains
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (.not.allocated(prec%iprcparm)) then
info = 1124
@ -206,7 +213,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_))

@ -167,7 +167,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_s_diag_precdescr(prec,iout,root, verbosity)
subroutine psb_s_diag_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
Implicit None
@ -176,11 +176,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='s_diag_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -201,6 +203,11 @@ contains
else
verbosity_ = 0
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt
@ -209,7 +216,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Diagonal scaling'
call psb_erractionsave(err_act)

@ -163,7 +163,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_s_null_precdescr(prec,iout,root, verbosity)
subroutine psb_s_null_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
@ -173,6 +173,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='s_null_precset'
@ -180,6 +181,7 @@ contains
integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -195,6 +197,11 @@ contains
else
root_ = psb_root_
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (present(verbosity)) then
verbosity_ = verbosity
else
@ -207,7 +214,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'No preconditioning'
9998 continue

@ -197,7 +197,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_sfile_prec_descr(prec,info,iout, root,verbosity)
subroutine psb_sfile_prec_descr(prec,info,iout, root,verbosity,prefix)
use psb_base_mod
implicit none
class(psb_sprec_type), intent(in) :: prec
@ -205,6 +205,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: iout_, verbosity_
character(len=20) :: name='prec_descr'
@ -219,7 +220,7 @@ contains
info = 1124
call psb_errpush(info,name,a_err="preconditioner")
end if
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity,prefix=prefix)
end subroutine psb_sfile_prec_descr

@ -161,17 +161,17 @@ module psb_z_base_prec_mod
abstract interface
subroutine psb_z_base_precdescr(prec,iout,root, verbosity)
subroutine psb_z_base_precdescr(prec,iout,root, verbosity,prefix)
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_sparse_mat
Implicit None
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 :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
end subroutine psb_z_base_precdescr
end interface

@ -158,7 +158,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_z_bjac_precdescr(prec,iout,root, verbosity)
subroutine psb_z_bjac_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
implicit none
@ -167,11 +167,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='z_bjac_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -194,6 +196,11 @@ contains
verbosity_ = 0
end if
if (verbosity_ < 0) goto 9998
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (.not.allocated(prec%iprcparm)) then
info = 1124
@ -206,7 +213,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Block Jacobi with: ',&
& fact_names(prec%iprcparm(psb_f_type_))

@ -167,7 +167,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_z_diag_precdescr(prec,iout,root, verbosity)
subroutine psb_z_diag_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
Implicit None
@ -176,11 +176,13 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='z_diag_precdescr'
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -201,6 +203,11 @@ contains
else
verbosity_ = 0
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (verbosity_ < 0) goto 9998
ctxt = prec%ctxt
@ -209,7 +216,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'Diagonal scaling'
call psb_erractionsave(err_act)

@ -163,7 +163,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_z_null_precdescr(prec,iout,root, verbosity)
subroutine psb_z_null_precdescr(prec,iout,root, verbosity,prefix)
use psb_penv_mod
use psb_error_mod
@ -173,6 +173,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: err_act, nrow, info
character(len=20) :: name='z_null_precset'
@ -180,6 +181,7 @@ contains
integer(psb_ipk_) :: ni
type(psb_ctxt_type) :: ctxt
integer(psb_ipk_) :: iout_, iam, np, root_, verbosity_
character(1024) :: prefix_
call psb_erractionsave(err_act)
@ -195,6 +197,11 @@ contains
else
root_ = psb_root_
end if
if (present(prefix)) then
prefix_ = prefix
else
prefix_ = ""
end if
if (present(verbosity)) then
verbosity_ = verbosity
else
@ -207,7 +214,7 @@ contains
if (root_ == -1) root_ = iam
if (iam == root_) &
& write(iout_,*) trim(prec%desc_prefix()),' ',&
& write(iout_,*) trim(prefix_),' ', trim(prec%desc_prefix()),' ',&
& 'No preconditioning'
9998 continue

@ -197,7 +197,7 @@ contains
! 0: normal
! >1: increased details
!
subroutine psb_zfile_prec_descr(prec,info,iout, root,verbosity)
subroutine psb_zfile_prec_descr(prec,info,iout, root,verbosity,prefix)
use psb_base_mod
implicit none
class(psb_zprec_type), intent(in) :: prec
@ -205,6 +205,7 @@ contains
integer(psb_ipk_), intent(in), optional :: iout
integer(psb_ipk_), intent(in), optional :: root
integer(psb_ipk_), intent(in), optional :: verbosity
character(len=*), intent(in), optional :: prefix
integer(psb_ipk_) :: iout_, verbosity_
character(len=20) :: name='prec_descr'
@ -219,7 +220,7 @@ contains
info = 1124
call psb_errpush(info,name,a_err="preconditioner")
end if
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity)
call prec%prec%descr(iout=iout,root=root, verbosity=verbosity,prefix=prefix)
end subroutine psb_zfile_prec_descr

Loading…
Cancel
Save