prec/impl/psb_c_bjacprec_impl.f90
 prec/impl/psb_d_bjacprec_impl.f90
 prec/impl/psb_s_bjacprec_impl.f90
 prec/impl/psb_z_bjacprec_impl.f90
 prec/psb_c_base_prec_mod.f90
 prec/psb_c_bjacprec.f90
 prec/psb_c_diagprec.f90
 prec/psb_c_nullprec.f90
 prec/psb_d_base_prec_mod.f90
 prec/psb_d_bjacprec.f90
 prec/psb_d_diagprec.f90
 prec/psb_d_nullprec.f90
 prec/psb_s_base_prec_mod.f90
 prec/psb_s_bjacprec.f90
 prec/psb_s_diagprec.f90
 prec/psb_s_nullprec.f90
 prec/psb_z_base_prec_mod.f90
 prec/psb_z_bjacprec.f90
 prec/psb_z_diagprec.f90
 prec/psb_z_nullprec.f90

Cray FTN does not like interface name same as subroutine name.
psblas3-type-indexed
Salvatore Filippone 13 years ago
parent a68120d320
commit 6f542b538b

@ -31,8 +31,8 @@ subroutine psb_c_bjac_dump(prec,info,prefix,head)
if (prec%av(psb_l_pr_)%is_asb()) &
& call prec%av(psb_l_pr_)%print(fname,head=head)
write(fname(lname+1:),'(a,a)')'_diag.mtx'
if (allocated(prec%d)) &
& call psb_geprt(fname,prec%d,head=head)
if (allocated(prec%dv)) &
& call psb_geprt(fname,prec%dv%v%v,head=head)
write(fname(lname+1:),'(a)')'_upper.mtx'
if (prec%av(psb_u_pr_)%is_asb()) &
& call prec%av(psb_u_pr_)%print(fname,head=head)
@ -503,7 +503,7 @@ subroutine psb_c_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
call prec%av(psb_l_pr_)%trim()
call prec%av(psb_u_pr_)%trim()
call prec%dv%bld(dd)
call move_alloc(dd,prec%d)
! call move_alloc(dd,prec%d)
else
info=psb_err_from_subroutine_
ch_err='psb_ilu_fct'

@ -31,8 +31,8 @@ subroutine psb_d_bjac_dump(prec,info,prefix,head)
if (prec%av(psb_l_pr_)%is_asb()) &
& call prec%av(psb_l_pr_)%print(fname,head=head)
write(fname(lname+1:),'(a,a)')'_diag.mtx'
if (allocated(prec%d)) &
& call psb_geprt(fname,prec%d,head=head)
if (allocated(prec%dv)) &
& call psb_geprt(fname,prec%dv%v%v,head=head)
write(fname(lname+1:),'(a)')'_upper.mtx'
if (prec%av(psb_u_pr_)%is_asb()) &
& call prec%av(psb_u_pr_)%print(fname,head=head)
@ -503,7 +503,7 @@ subroutine psb_d_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
call prec%av(psb_l_pr_)%trim()
call prec%av(psb_u_pr_)%trim()
call prec%dv%bld(dd)
call move_alloc(dd,prec%d)
! call move_alloc(dd,prec%d)
else
info=psb_err_from_subroutine_
ch_err='psb_ilu_fct'

@ -31,8 +31,8 @@ subroutine psb_s_bjac_dump(prec,info,prefix,head)
if (prec%av(psb_l_pr_)%is_asb()) &
& call prec%av(psb_l_pr_)%print(fname,head=head)
write(fname(lname+1:),'(a,a)')'_diag.mtx'
if (allocated(prec%d)) &
& call psb_geprt(fname,prec%d,head=head)
if (allocated(prec%dv)) &
& call psb_geprt(fname,prec%dv%v%v,head=head)
write(fname(lname+1:),'(a)')'_upper.mtx'
if (prec%av(psb_u_pr_)%is_asb()) &
& call prec%av(psb_u_pr_)%print(fname,head=head)
@ -503,7 +503,7 @@ subroutine psb_s_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
call prec%av(psb_l_pr_)%trim()
call prec%av(psb_u_pr_)%trim()
call prec%dv%bld(dd)
call move_alloc(dd,prec%d)
! call move_alloc(dd,prec%d)
else
info=psb_err_from_subroutine_
ch_err='psb_ilu_fct'

@ -31,8 +31,8 @@ subroutine psb_z_bjac_dump(prec,info,prefix,head)
if (prec%av(psb_l_pr_)%is_asb()) &
& call prec%av(psb_l_pr_)%print(fname,head=head)
write(fname(lname+1:),'(a,a)')'_diag.mtx'
if (allocated(prec%d)) &
& call psb_geprt(fname,prec%d,head=head)
if (allocated(prec%dv)) &
& call psb_geprt(fname,prec%dv%v%v,head=head)
write(fname(lname+1:),'(a)')'_upper.mtx'
if (prec%av(psb_u_pr_)%is_asb()) &
& call prec%av(psb_u_pr_)%print(fname,head=head)
@ -503,7 +503,7 @@ subroutine psb_z_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
call prec%av(psb_l_pr_)%trim()
call prec%av(psb_u_pr_)%trim()
call prec%dv%bld(dd)
call move_alloc(dd,prec%d)
! call move_alloc(dd,prec%d)
else
info=psb_err_from_subroutine_
ch_err='psb_ilu_fct'

@ -38,6 +38,7 @@ module psb_c_base_prec_mod
! Reduces size of .mod file.
use psb_base_mod, only : psb_spk_, psb_long_int_k_,&
& psb_desc_type, psb_sizeof, psb_free, psb_cdfree, psb_errpush, psb_act_abort_,&
& psb_sizeof_int, psb_sizeof_long_int, psb_sizeof_sp, psb_sizeof_dp, &
& psb_erractionsave, psb_erractionrestore, psb_error, psb_get_errstatus, psb_success_,&
& psb_c_base_sparse_mat, psb_cspmat_type, psb_c_csr_sparse_mat,&
& psb_c_base_vect_type, psb_c_vect_type

@ -5,7 +5,6 @@ module psb_c_bjacprec
type, extends(psb_c_base_prec_type) :: psb_c_bjac_prec_type
integer, allocatable :: iprcparm(:)
type(psb_cspmat_type), allocatable :: av(:)
complex(psb_spk_), allocatable :: d(:)
type(psb_c_vect_type), allocatable :: dv
contains
procedure, pass(prec) :: c_apply_v => psb_c_bjac_apply_vect
@ -30,16 +29,16 @@ module psb_c_bjacprec
& 'ILU(eps) '/)
interface psb_c_bjac_dump
interface
subroutine psb_c_bjac_dump(prec,info,prefix,head)
import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
class(psb_c_bjac_prec_type), intent(in) :: prec
integer, intent(out) :: info
character(len=*), intent(in), optional :: prefix,head
end subroutine psb_c_bjac_dump
end interface psb_c_bjac_dump
end interface
interface psb_c_bjac_apply_vect
interface
subroutine psb_c_bjac_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -51,9 +50,9 @@ module psb_c_bjacprec
character(len=1), optional :: trans
complex(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_c_bjac_apply_vect
end interface psb_c_bjac_apply_vect
end interface
interface psb_c_bjac_apply
interface
subroutine psb_c_bjac_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
@ -66,17 +65,17 @@ module psb_c_bjacprec
character(len=1), optional :: trans
complex(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_c_bjac_apply
end interface psb_c_bjac_apply
end interface
interface psb_c_bjac_precinit
interface
subroutine psb_c_bjac_precinit(prec,info)
import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
class(psb_c_bjac_prec_type),intent(inout) :: prec
integer, intent(out) :: info
end subroutine psb_c_bjac_precinit
end interface psb_c_bjac_precinit
end interface
interface psb_c_bjac_precbld
interface
subroutine psb_c_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_, &
& psb_cspmat_type, psb_c_base_sparse_mat, psb_c_base_vect_type
@ -89,9 +88,9 @@ module psb_c_bjacprec
class(psb_c_base_sparse_mat), intent(in), optional :: amold
class(psb_c_base_vect_type), intent(in), optional :: vmold
end subroutine psb_c_bjac_precbld
end interface psb_c_bjac_precbld
end interface
interface psb_c_bjac_precseti
interface
subroutine psb_c_bjac_precseti(prec,what,val,info)
import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
class(psb_c_bjac_prec_type),intent(inout) :: prec
@ -99,9 +98,9 @@ module psb_c_bjacprec
integer, intent(in) :: val
integer, intent(out) :: info
end subroutine psb_c_bjac_precseti
end interface psb_c_bjac_precseti
end interface
!!$ interface psb_c_bjac_precsetr
!!$ interface
!!$ subroutine psb_c_bjac_precsetr(prec,what,val,info)
!!$ import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
!!$ class(psb_c_bjac_prec_type),intent(inout) :: prec
@ -109,9 +108,9 @@ module psb_c_bjacprec
!!$ real(psb_spk_), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_c_bjac_precsetr
!!$ end interface psb_c_bjac_precsetr
!!$ end interface
!!$
!!$ interface psb_c_bjac_precsetc
!!$ interface
!!$ subroutine psb_c_bjac_precsetc(prec,what,val,info)
!!$ import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
!!$ class(psb_c_bjac_prec_type),intent(inout) :: prec
@ -119,15 +118,15 @@ module psb_c_bjacprec
!!$ character(len=*), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_c_bjac_precsetc
!!$ end interface psb_c_bjac_precsetc
!!$ end interface
!!$
!!$ interface psb_c_bjac_precfree
!!$ interface
!!$ subroutine psb_c_bjac_precfree(prec,info)
!!$ import :: psb_desc_type, psb_c_bjac_prec_type, psb_c_vect_type, psb_spk_
!!$ class(psb_c_bjac_prec_type), intent(inout) :: prec
!!$ integer, intent(out) :: info
!!$ end subroutine psb_c_bjac_precfree
!!$ end interface psb_c_bjac_precfree
!!$ end interface
contains
@ -280,9 +279,7 @@ contains
enddo
deallocate(prec%av,stat=info)
end if
if (allocated(prec%d)) then
deallocate(prec%d,stat=info)
end if
if (allocated(prec%dv)) then
call prec%dv%free(info)
if (info == 0) deallocate(prec%dv,stat=info)

@ -26,7 +26,7 @@ module psb_c_diagprec
interface psb_c_diag_apply_vect
interface
subroutine psb_c_diag_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_c_diag_prec_type, psb_c_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -38,9 +38,9 @@ module psb_c_diagprec
character(len=1), optional :: trans
complex(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_c_diag_apply_vect
end interface psb_c_diag_apply_vect
end interface
interface psb_c_diag_apply
interface
subroutine psb_c_diag_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_c_diag_prec_type, psb_c_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -52,9 +52,9 @@ module psb_c_diagprec
character(len=1), optional :: trans
complex(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_c_diag_apply
end interface psb_c_diag_apply
end interface
interface psb_c_diag_precbld
interface
subroutine psb_c_diag_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_c_diag_prec_type, psb_c_vect_type, psb_spk_, &
& psb_cspmat_type, psb_c_base_sparse_mat, psb_c_base_vect_type
@ -67,7 +67,7 @@ module psb_c_diagprec
class(psb_c_base_sparse_mat), intent(in), optional :: amold
class(psb_c_base_vect_type), intent(in), optional :: vmold
end subroutine psb_c_diag_precbld
end interface psb_c_diag_precbld
end interface
contains

@ -21,7 +21,7 @@ module psb_c_nullprec
& psb_c_null_precinit, psb_c_null_precfree, psb_c_null_precdescr
interface psb_c_null_apply_vect
interface
subroutine psb_c_null_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_c_null_prec_type, psb_c_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -32,11 +32,10 @@ module psb_c_nullprec
integer, intent(out) :: info
character(len=1), optional :: trans
complex(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_c_null_apply_vect
end interface psb_c_null_apply_vect
end interface
interface psb_c_null_apply
interface
subroutine psb_c_null_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_c_null_prec_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -48,7 +47,7 @@ module psb_c_nullprec
character(len=1), optional :: trans
complex(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_c_null_apply
end interface psb_c_null_apply
end interface
contains

@ -38,6 +38,7 @@ module psb_d_base_prec_mod
! Reduces size of .mod file.
use psb_base_mod, only : psb_dpk_, psb_long_int_k_,&
& psb_desc_type, psb_sizeof, psb_free, psb_cdfree, psb_errpush, psb_act_abort_,&
& psb_sizeof_int, psb_sizeof_long_int, psb_sizeof_sp, psb_sizeof_dp, &
& psb_erractionsave, psb_erractionrestore, psb_error, psb_get_errstatus, psb_success_,&
& psb_d_base_sparse_mat, psb_dspmat_type, psb_d_csr_sparse_mat,&
& psb_d_base_vect_type, psb_d_vect_type

@ -5,7 +5,6 @@ module psb_d_bjacprec
type, extends(psb_d_base_prec_type) :: psb_d_bjac_prec_type
integer, allocatable :: iprcparm(:)
type(psb_dspmat_type), allocatable :: av(:)
real(psb_dpk_), allocatable :: d(:)
type(psb_d_vect_type), allocatable :: dv
contains
procedure, pass(prec) :: d_apply_v => psb_d_bjac_apply_vect
@ -30,16 +29,16 @@ module psb_d_bjacprec
& 'ILU(eps) '/)
interface psb_d_bjac_dump
interface
subroutine psb_d_bjac_dump(prec,info,prefix,head)
import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
class(psb_d_bjac_prec_type), intent(in) :: prec
integer, intent(out) :: info
character(len=*), intent(in), optional :: prefix,head
end subroutine psb_d_bjac_dump
end interface psb_d_bjac_dump
end interface
interface psb_d_bjac_apply_vect
interface
subroutine psb_d_bjac_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -51,9 +50,9 @@ module psb_d_bjacprec
character(len=1), optional :: trans
real(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_d_bjac_apply_vect
end interface psb_d_bjac_apply_vect
end interface
interface psb_d_bjac_apply
interface
subroutine psb_d_bjac_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
@ -66,17 +65,17 @@ module psb_d_bjacprec
character(len=1), optional :: trans
real(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_d_bjac_apply
end interface psb_d_bjac_apply
end interface
interface psb_d_bjac_precinit
interface
subroutine psb_d_bjac_precinit(prec,info)
import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
class(psb_d_bjac_prec_type),intent(inout) :: prec
integer, intent(out) :: info
end subroutine psb_d_bjac_precinit
end interface psb_d_bjac_precinit
end interface
interface psb_d_bjac_precbld
interface
subroutine psb_d_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_, &
& psb_dspmat_type, psb_d_base_sparse_mat, psb_d_base_vect_type
@ -89,9 +88,9 @@ module psb_d_bjacprec
class(psb_d_base_sparse_mat), intent(in), optional :: amold
class(psb_d_base_vect_type), intent(in), optional :: vmold
end subroutine psb_d_bjac_precbld
end interface psb_d_bjac_precbld
end interface
interface psb_d_bjac_precseti
interface
subroutine psb_d_bjac_precseti(prec,what,val,info)
import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
class(psb_d_bjac_prec_type),intent(inout) :: prec
@ -99,9 +98,9 @@ module psb_d_bjacprec
integer, intent(in) :: val
integer, intent(out) :: info
end subroutine psb_d_bjac_precseti
end interface psb_d_bjac_precseti
end interface
!!$ interface psb_d_bjac_precsetr
!!$ interface
!!$ subroutine psb_d_bjac_precsetr(prec,what,val,info)
!!$ import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
!!$ class(psb_d_bjac_prec_type),intent(inout) :: prec
@ -109,9 +108,9 @@ module psb_d_bjacprec
!!$ real(psb_dpk_), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_d_bjac_precsetr
!!$ end interface psb_d_bjac_precsetr
!!$ end interface
!!$
!!$ interface psb_d_bjac_precsetc
!!$ interface
!!$ subroutine psb_d_bjac_precsetc(prec,what,val,info)
!!$ import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
!!$ class(psb_d_bjac_prec_type),intent(inout) :: prec
@ -119,15 +118,15 @@ module psb_d_bjacprec
!!$ character(len=*), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_d_bjac_precsetc
!!$ end interface psb_d_bjac_precsetc
!!$ end interface
!!$
!!$ interface psb_d_bjac_precfree
!!$ interface
!!$ subroutine psb_d_bjac_precfree(prec,info)
!!$ import :: psb_desc_type, psb_d_bjac_prec_type, psb_d_vect_type, psb_dpk_
!!$ class(psb_d_bjac_prec_type), intent(inout) :: prec
!!$ integer, intent(out) :: info
!!$ end subroutine psb_d_bjac_precfree
!!$ end interface psb_d_bjac_precfree
!!$ end interface
contains
@ -280,9 +279,7 @@ contains
enddo
deallocate(prec%av,stat=info)
end if
if (allocated(prec%d)) then
deallocate(prec%d,stat=info)
end if
if (allocated(prec%dv)) then
call prec%dv%free(info)
if (info == 0) deallocate(prec%dv,stat=info)

@ -26,7 +26,7 @@ module psb_d_diagprec
interface psb_d_diag_apply_vect
interface
subroutine psb_d_diag_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_d_diag_prec_type, psb_d_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -38,9 +38,9 @@ module psb_d_diagprec
character(len=1), optional :: trans
real(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_d_diag_apply_vect
end interface psb_d_diag_apply_vect
end interface
interface psb_d_diag_apply
interface
subroutine psb_d_diag_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_d_diag_prec_type, psb_d_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -52,9 +52,9 @@ module psb_d_diagprec
character(len=1), optional :: trans
real(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_d_diag_apply
end interface psb_d_diag_apply
end interface
interface psb_d_diag_precbld
interface
subroutine psb_d_diag_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_d_diag_prec_type, psb_d_vect_type, psb_dpk_, &
& psb_dspmat_type, psb_d_base_sparse_mat, psb_d_base_vect_type
@ -67,7 +67,7 @@ module psb_d_diagprec
class(psb_d_base_sparse_mat), intent(in), optional :: amold
class(psb_d_base_vect_type), intent(in), optional :: vmold
end subroutine psb_d_diag_precbld
end interface psb_d_diag_precbld
end interface
contains

@ -21,7 +21,7 @@ module psb_d_nullprec
& psb_d_null_precinit, psb_d_null_precfree, psb_d_null_precdescr
interface psb_d_null_apply_vect
interface
subroutine psb_d_null_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_d_null_prec_type, psb_d_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -32,11 +32,10 @@ module psb_d_nullprec
integer, intent(out) :: info
character(len=1), optional :: trans
real(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_d_null_apply_vect
end interface psb_d_null_apply_vect
end interface
interface psb_d_null_apply
interface
subroutine psb_d_null_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_d_null_prec_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -48,7 +47,7 @@ module psb_d_nullprec
character(len=1), optional :: trans
real(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_d_null_apply
end interface psb_d_null_apply
end interface
contains

@ -38,6 +38,7 @@ module psb_s_base_prec_mod
! Reduces size of .mod file.
use psb_base_mod, only : psb_spk_, psb_long_int_k_,&
& psb_desc_type, psb_sizeof, psb_free, psb_cdfree, psb_errpush, psb_act_abort_,&
& psb_sizeof_int, psb_sizeof_long_int, psb_sizeof_sp, psb_sizeof_dp, &
& psb_erractionsave, psb_erractionrestore, psb_error, psb_get_errstatus, psb_success_,&
& psb_s_base_sparse_mat, psb_sspmat_type, psb_s_csr_sparse_mat,&
& psb_s_base_vect_type, psb_s_vect_type

@ -5,7 +5,6 @@ module psb_s_bjacprec
type, extends(psb_s_base_prec_type) :: psb_s_bjac_prec_type
integer, allocatable :: iprcparm(:)
type(psb_sspmat_type), allocatable :: av(:)
real(psb_spk_), allocatable :: d(:)
type(psb_s_vect_type), allocatable :: dv
contains
procedure, pass(prec) :: s_apply_v => psb_s_bjac_apply_vect
@ -30,16 +29,16 @@ module psb_s_bjacprec
& 'ILU(eps) '/)
interface psb_s_bjac_dump
interface
subroutine psb_s_bjac_dump(prec,info,prefix,head)
import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
class(psb_s_bjac_prec_type), intent(in) :: prec
integer, intent(out) :: info
character(len=*), intent(in), optional :: prefix,head
end subroutine psb_s_bjac_dump
end interface psb_s_bjac_dump
end interface
interface psb_s_bjac_apply_vect
interface
subroutine psb_s_bjac_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -51,9 +50,9 @@ module psb_s_bjacprec
character(len=1), optional :: trans
real(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_s_bjac_apply_vect
end interface psb_s_bjac_apply_vect
end interface
interface psb_s_bjac_apply
interface
subroutine psb_s_bjac_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
@ -66,17 +65,17 @@ module psb_s_bjacprec
character(len=1), optional :: trans
real(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_s_bjac_apply
end interface psb_s_bjac_apply
end interface
interface psb_s_bjac_precinit
interface
subroutine psb_s_bjac_precinit(prec,info)
import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
class(psb_s_bjac_prec_type),intent(inout) :: prec
integer, intent(out) :: info
end subroutine psb_s_bjac_precinit
end interface psb_s_bjac_precinit
end interface
interface psb_s_bjac_precbld
interface
subroutine psb_s_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_, &
& psb_sspmat_type, psb_s_base_sparse_mat, psb_s_base_vect_type
@ -89,9 +88,9 @@ module psb_s_bjacprec
class(psb_s_base_sparse_mat), intent(in), optional :: amold
class(psb_s_base_vect_type), intent(in), optional :: vmold
end subroutine psb_s_bjac_precbld
end interface psb_s_bjac_precbld
end interface
interface psb_s_bjac_precseti
interface
subroutine psb_s_bjac_precseti(prec,what,val,info)
import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
class(psb_s_bjac_prec_type),intent(inout) :: prec
@ -99,9 +98,9 @@ module psb_s_bjacprec
integer, intent(in) :: val
integer, intent(out) :: info
end subroutine psb_s_bjac_precseti
end interface psb_s_bjac_precseti
end interface
!!$ interface psb_s_bjac_precsetr
!!$ interface
!!$ subroutine psb_s_bjac_precsetr(prec,what,val,info)
!!$ import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
!!$ class(psb_s_bjac_prec_type),intent(inout) :: prec
@ -109,9 +108,9 @@ module psb_s_bjacprec
!!$ real(psb_spk_), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_s_bjac_precsetr
!!$ end interface psb_s_bjac_precsetr
!!$ end interface
!!$
!!$ interface psb_s_bjac_precsetc
!!$ interface
!!$ subroutine psb_s_bjac_precsetc(prec,what,val,info)
!!$ import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
!!$ class(psb_s_bjac_prec_type),intent(inout) :: prec
@ -119,15 +118,15 @@ module psb_s_bjacprec
!!$ character(len=*), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_s_bjac_precsetc
!!$ end interface psb_s_bjac_precsetc
!!$ end interface
!!$
!!$ interface psb_s_bjac_precfree
!!$ interface
!!$ subroutine psb_s_bjac_precfree(prec,info)
!!$ import :: psb_desc_type, psb_s_bjac_prec_type, psb_s_vect_type, psb_spk_
!!$ class(psb_s_bjac_prec_type), intent(inout) :: prec
!!$ integer, intent(out) :: info
!!$ end subroutine psb_s_bjac_precfree
!!$ end interface psb_s_bjac_precfree
!!$ end interface
contains
@ -280,9 +279,7 @@ contains
enddo
deallocate(prec%av,stat=info)
end if
if (allocated(prec%d)) then
deallocate(prec%d,stat=info)
end if
if (allocated(prec%dv)) then
call prec%dv%free(info)
if (info == 0) deallocate(prec%dv,stat=info)

@ -26,7 +26,7 @@ module psb_s_diagprec
interface psb_s_diag_apply_vect
interface
subroutine psb_s_diag_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_s_diag_prec_type, psb_s_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -38,9 +38,9 @@ module psb_s_diagprec
character(len=1), optional :: trans
real(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_s_diag_apply_vect
end interface psb_s_diag_apply_vect
end interface
interface psb_s_diag_apply
interface
subroutine psb_s_diag_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_s_diag_prec_type, psb_s_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -52,9 +52,9 @@ module psb_s_diagprec
character(len=1), optional :: trans
real(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_s_diag_apply
end interface psb_s_diag_apply
end interface
interface psb_s_diag_precbld
interface
subroutine psb_s_diag_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_s_diag_prec_type, psb_s_vect_type, psb_spk_, &
& psb_sspmat_type, psb_s_base_sparse_mat, psb_s_base_vect_type
@ -67,7 +67,7 @@ module psb_s_diagprec
class(psb_s_base_sparse_mat), intent(in), optional :: amold
class(psb_s_base_vect_type), intent(in), optional :: vmold
end subroutine psb_s_diag_precbld
end interface psb_s_diag_precbld
end interface
contains

@ -21,7 +21,7 @@ module psb_s_nullprec
& psb_s_null_precinit, psb_s_null_precfree, psb_s_null_precdescr
interface psb_s_null_apply_vect
interface
subroutine psb_s_null_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_s_null_prec_type, psb_s_vect_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -32,11 +32,10 @@ module psb_s_nullprec
integer, intent(out) :: info
character(len=1), optional :: trans
real(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_s_null_apply_vect
end interface psb_s_null_apply_vect
end interface
interface psb_s_null_apply
interface
subroutine psb_s_null_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_s_null_prec_type, psb_spk_
type(psb_desc_type),intent(in) :: desc_data
@ -48,7 +47,7 @@ module psb_s_nullprec
character(len=1), optional :: trans
real(psb_spk_),intent(inout), optional, target :: work(:)
end subroutine psb_s_null_apply
end interface psb_s_null_apply
end interface
contains

@ -38,6 +38,7 @@ module psb_z_base_prec_mod
! Reduces size of .mod file.
use psb_base_mod, only : psb_dpk_, psb_long_int_k_,&
& psb_desc_type, psb_sizeof, psb_free, psb_cdfree, psb_errpush, psb_act_abort_,&
& psb_sizeof_int, psb_sizeof_long_int, psb_sizeof_sp, psb_sizeof_dp, &
& psb_erractionsave, psb_erractionrestore, psb_error, psb_get_errstatus, psb_success_,&
& psb_z_base_sparse_mat, psb_zspmat_type, psb_z_csr_sparse_mat,&
& psb_z_base_vect_type, psb_z_vect_type

@ -5,7 +5,6 @@ module psb_z_bjacprec
type, extends(psb_z_base_prec_type) :: psb_z_bjac_prec_type
integer, allocatable :: iprcparm(:)
type(psb_zspmat_type), allocatable :: av(:)
complex(psb_dpk_), allocatable :: d(:)
type(psb_z_vect_type), allocatable :: dv
contains
procedure, pass(prec) :: z_apply_v => psb_z_bjac_apply_vect
@ -30,16 +29,16 @@ module psb_z_bjacprec
& 'ILU(eps) '/)
interface psb_z_bjac_dump
interface
subroutine psb_z_bjac_dump(prec,info,prefix,head)
import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
class(psb_z_bjac_prec_type), intent(in) :: prec
integer, intent(out) :: info
character(len=*), intent(in), optional :: prefix,head
end subroutine psb_z_bjac_dump
end interface psb_z_bjac_dump
end interface
interface psb_z_bjac_apply_vect
interface
subroutine psb_z_bjac_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -51,9 +50,9 @@ module psb_z_bjacprec
character(len=1), optional :: trans
complex(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_z_bjac_apply_vect
end interface psb_z_bjac_apply_vect
end interface
interface psb_z_bjac_apply
interface
subroutine psb_z_bjac_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
@ -66,17 +65,17 @@ module psb_z_bjacprec
character(len=1), optional :: trans
complex(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_z_bjac_apply
end interface psb_z_bjac_apply
end interface
interface psb_z_bjac_precinit
interface
subroutine psb_z_bjac_precinit(prec,info)
import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
class(psb_z_bjac_prec_type),intent(inout) :: prec
integer, intent(out) :: info
end subroutine psb_z_bjac_precinit
end interface psb_z_bjac_precinit
end interface
interface psb_z_bjac_precbld
interface
subroutine psb_z_bjac_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_, &
& psb_zspmat_type, psb_z_base_sparse_mat, psb_z_base_vect_type
@ -89,9 +88,9 @@ module psb_z_bjacprec
class(psb_z_base_sparse_mat), intent(in), optional :: amold
class(psb_z_base_vect_type), intent(in), optional :: vmold
end subroutine psb_z_bjac_precbld
end interface psb_z_bjac_precbld
end interface
interface psb_z_bjac_precseti
interface
subroutine psb_z_bjac_precseti(prec,what,val,info)
import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
class(psb_z_bjac_prec_type),intent(inout) :: prec
@ -99,9 +98,9 @@ module psb_z_bjacprec
integer, intent(in) :: val
integer, intent(out) :: info
end subroutine psb_z_bjac_precseti
end interface psb_z_bjac_precseti
end interface
!!$ interface psb_z_bjac_precsetr
!!$ interface
!!$ subroutine psb_z_bjac_precsetr(prec,what,val,info)
!!$ import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
!!$ class(psb_z_bjac_prec_type),intent(inout) :: prec
@ -109,9 +108,9 @@ module psb_z_bjacprec
!!$ real(psb_dpk_), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_z_bjac_precsetr
!!$ end interface psb_z_bjac_precsetr
!!$ end interface
!!$
!!$ interface psb_z_bjac_precsetc
!!$ interface
!!$ subroutine psb_z_bjac_precsetc(prec,what,val,info)
!!$ import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
!!$ class(psb_z_bjac_prec_type),intent(inout) :: prec
@ -119,15 +118,15 @@ module psb_z_bjacprec
!!$ character(len=*), intent(in) :: val
!!$ integer, intent(out) :: info
!!$ end subroutine psb_z_bjac_precsetc
!!$ end interface psb_z_bjac_precsetc
!!$ end interface
!!$
!!$ interface psb_z_bjac_precfree
!!$ interface
!!$ subroutine psb_z_bjac_precfree(prec,info)
!!$ import :: psb_desc_type, psb_z_bjac_prec_type, psb_z_vect_type, psb_dpk_
!!$ class(psb_z_bjac_prec_type), intent(inout) :: prec
!!$ integer, intent(out) :: info
!!$ end subroutine psb_z_bjac_precfree
!!$ end interface psb_z_bjac_precfree
!!$ end interface
contains
@ -280,9 +279,7 @@ contains
enddo
deallocate(prec%av,stat=info)
end if
if (allocated(prec%d)) then
deallocate(prec%d,stat=info)
end if
if (allocated(prec%dv)) then
call prec%dv%free(info)
if (info == 0) deallocate(prec%dv,stat=info)

@ -26,7 +26,7 @@ module psb_z_diagprec
interface psb_z_diag_apply_vect
interface
subroutine psb_z_diag_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_z_diag_prec_type, psb_z_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -38,9 +38,9 @@ module psb_z_diagprec
character(len=1), optional :: trans
complex(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_z_diag_apply_vect
end interface psb_z_diag_apply_vect
end interface
interface psb_z_diag_apply
interface
subroutine psb_z_diag_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_z_diag_prec_type, psb_z_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -52,9 +52,9 @@ module psb_z_diagprec
character(len=1), optional :: trans
complex(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_z_diag_apply
end interface psb_z_diag_apply
end interface
interface psb_z_diag_precbld
interface
subroutine psb_z_diag_precbld(a,desc_a,prec,info,upd,amold,afmt,vmold)
import :: psb_desc_type, psb_z_diag_prec_type, psb_z_vect_type, psb_dpk_, &
& psb_zspmat_type, psb_z_base_sparse_mat, psb_z_base_vect_type
@ -67,7 +67,7 @@ module psb_z_diagprec
class(psb_z_base_sparse_mat), intent(in), optional :: amold
class(psb_z_base_vect_type), intent(in), optional :: vmold
end subroutine psb_z_diag_precbld
end interface psb_z_diag_precbld
end interface
contains

@ -21,7 +21,7 @@ module psb_z_nullprec
& psb_z_null_precinit, psb_z_null_precfree, psb_z_null_precdescr
interface psb_z_null_apply_vect
interface
subroutine psb_z_null_apply_vect(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_z_null_prec_type, psb_z_vect_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -32,11 +32,10 @@ module psb_z_nullprec
integer, intent(out) :: info
character(len=1), optional :: trans
complex(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_z_null_apply_vect
end interface psb_z_null_apply_vect
end interface
interface psb_z_null_apply
interface
subroutine psb_z_null_apply(alpha,prec,x,beta,y,desc_data,info,trans,work)
import :: psb_desc_type, psb_z_null_prec_type, psb_dpk_
type(psb_desc_type),intent(in) :: desc_data
@ -48,7 +47,7 @@ module psb_z_nullprec
character(len=1), optional :: trans
complex(psb_dpk_),intent(inout), optional, target :: work(:)
end subroutine psb_z_null_apply
end interface psb_z_null_apply
end interface
contains

Loading…
Cancel
Save