base/modules/Makefile
 krylov/psb_dbicg.f90
 krylov/psb_dcg.F90
 krylov/psb_dcgs.f90
 krylov/psb_dcgstab.F90
 krylov/psb_dcgstabl.f90
 krylov/psb_drgmres.f90
 krylov/psb_krylov_mod.f90
 prec/psb_dbjac_aply.f90
 prec/psb_dbjac_bld.f90
 prec/psb_ddiagsc_bld.f90
 prec/psb_dilu_fct.f90
 prec/psb_dprecbld.f90
 prec/psb_prec_mod.f90
 prec/psb_prec_type.f90
 util/psb_mat_dist_mod.f90


Preparing for switchover to psb_, step 7
psblas3-type-indexed
Salvatore Filippone 15 years ago
parent f95297a077
commit 5a6b34de32

@ -26,7 +26,8 @@ lib: $(BASIC_MODS) blacsmod $(UTIL_MODS) $(OBJS) $(LIBMOD)
/bin/cp -p *$(.mod) $(LIBDIR)
psbn_d_base_mat_mod.o: psb_string_mod.o psb_sort_mod.o psb_ip_reord_mod.o psb_error_mod.o
psbn_base_mat_mod.o: psb_string_mod.o psb_sort_mod.o psb_ip_reord_mod.o psb_error_mod.o
psbn_d_base_mat_mod.o: psbn_base_mat_mod.o
psbn_mat_mod.o: psbn_d_base_mat_mod.o psbn_d_csr_mat_mod.o
psb_realloc_mod.o : psb_error_mod.o
psb_spmat_type.o : psb_realloc_mod.o psb_error_mod.o psb_const_mod.o psb_string_mod.o psb_sort_mod.o

@ -98,9 +98,9 @@ subroutine psb_dbicg(a,prec,b,x,eps,desc_a,info,itmax,iter,err,itrace,istop)
use psb_base_mod
use psb_prec_mod
use psb_krylov_mod, psb_protect_name => psb_dbicg
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a
!!$ parameters
!!$ type(psb_dspmat_type), intent(in) :: a

@ -99,9 +99,9 @@ subroutine psb_dcg(a,prec,b,x,eps,desc_a,info,itmax,iter,err,itrace,istop,cond)
use psb_base_mod
use psb_prec_mod
use psb_krylov_mod, psb_protect_name => psb_dcg
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a

@ -98,9 +98,9 @@ Subroutine psb_dcgs(a,prec,b,x,eps,desc_a,info,itmax,iter,err,itrace,istop)
use psb_base_mod
use psb_prec_mod
use psb_krylov_mod, psb_protect_name => psb_dcgs
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a
!!$ parameters

@ -98,9 +98,9 @@ Subroutine psb_dcgstab(a,prec,b,x,eps,desc_a,info,itmax,iter,err,itrace,istop)
use psb_base_mod
use psb_prec_mod
use psb_krylov_mod, psb_protect_name => psb_dcgstab
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a
!!$ parameters

@ -107,9 +107,9 @@ Subroutine psb_dcgstabl(a,prec,b,x,eps,desc_a,info,itmax,iter,err,itrace,irst,is
use psb_base_mod
use psb_prec_mod
use psb_krylov_mod, psb_protect_name => psb_dcgstabl
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a
!!$ parameters

@ -110,9 +110,9 @@ subroutine psb_drgmres(a,prec,b,x,eps,desc_a,info,itmax,iter,err,itrace,irst,ist
use psb_base_mod
use psb_prec_mod
use psb_krylov_mod, psb_protect_name => psb_drgmres
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a
!!$ Parameters

@ -62,8 +62,8 @@ Module psb_krylov_mod
& desc_a,info,itmax,iter,err,itrace,istop,cond)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_mod, only : psb_dprec_type
use psbn_d_mat_mod
type(psbn_d_sparse_mat), intent(in) :: a
use psb_d_mat_mod
type(psb_d_sparse_mat), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
real(psb_dpk_), intent(in) :: b(:)
real(psb_dpk_), intent(inout) :: x(:)
@ -126,8 +126,8 @@ Module psb_krylov_mod
& desc_a,info,itmax,iter,err,itrace,istop)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_mod, only : psb_dprec_type
use psbn_d_mat_mod
type(psbn_d_sparse_mat), intent(in) :: a
use psb_d_mat_mod
type(psb_d_sparse_mat), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
real(psb_dpk_), intent(in) :: b(:)
real(psb_dpk_), intent(inout) :: x(:)
@ -190,8 +190,8 @@ Module psb_krylov_mod
& desc_a,info,itmax,iter,err,itrace,istop)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_mod, only : psb_dprec_type
use psbn_d_mat_mod
type(psbn_d_sparse_mat), intent(in) :: a
use psb_d_mat_mod
type(psb_d_sparse_mat), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
real(psb_dpk_), intent(in) :: b(:)
real(psb_dpk_), intent(inout) :: x(:)
@ -254,8 +254,8 @@ Module psb_krylov_mod
&itmax,iter,err, itrace,irst,istop)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_mod, only : psb_dprec_type
use psbn_d_mat_mod
type(psbn_d_sparse_mat), intent(in) :: a
use psb_d_mat_mod
type(psb_d_sparse_mat), intent(in) :: a
Type(psb_desc_type), Intent(in) :: desc_a
type(psb_dprec_type), intent(in) :: prec
Real(psb_dpk_), Intent(in) :: b(:)
@ -318,8 +318,8 @@ Module psb_krylov_mod
&itmax,iter,err,itrace,irst,istop)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_mod, only : psb_dprec_type
use psbn_d_mat_mod
type(psbn_d_sparse_mat), intent(in) :: a
use psb_d_mat_mod
type(psb_d_sparse_mat), intent(in) :: a
Type(psb_desc_type), Intent(in) :: desc_a
type(psb_dprec_type), intent(in) :: prec
Real(psb_dpk_), Intent(in) :: b(:)
@ -382,8 +382,8 @@ Module psb_krylov_mod
&itmax,iter,err,itrace,istop)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_mod, only : psb_dprec_type
use psbn_d_mat_mod
type(psbn_d_sparse_mat), intent(in) :: a
use psb_d_mat_mod
type(psb_d_sparse_mat), intent(in) :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dprec_type), intent(in) :: prec
real(psb_dpk_), intent(in) :: b(:)
@ -619,9 +619,9 @@ contains
use psb_base_mod
use psb_prec_mod,only : psb_sprec_type, psb_dprec_type, psb_cprec_type, psb_zprec_type
use psbn_d_mat_mod
use psb_d_mat_mod
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a
character(len=*) :: method
!!$ Type(psb_dspmat_type), Intent(in) :: a
@ -1068,9 +1068,9 @@ contains
subroutine psb_d_init_conv(methdname,stopc,trace,itmax,a,b,eps,desc_a,stopdat,info)
use psb_base_mod
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
type(psbn_d_sparse_mat), intent(in) :: a
type(psb_d_sparse_mat), intent(in) :: a
character(len=*), intent(in) :: methdname
integer, intent(in) :: stopc, trace,itmax
!!$ type(psb_dspmat_type), intent(in) :: a

@ -38,7 +38,7 @@ subroutine psb_dbjac_aply(alpha,prec,x,beta,y,desc_data,trans,work,info)
!
use psb_base_mod
use psbn_d_mat_mod
use psb_d_mat_mod
use psb_prec_mod, psb_protect_name => psb_dbjac_aply
implicit none

@ -30,7 +30,7 @@
!!$
!!$
subroutine psb_dbjac_bld(a,desc_a,p,upd,info)
use psbn_d_mat_mod
use psb_d_mat_mod
use psb_base_mod
use psb_prec_mod, psb_protect_name => psb_dbjac_bld
implicit none
@ -38,7 +38,7 @@ subroutine psb_dbjac_bld(a,desc_a,p,upd,info)
! .. Scalar Arguments ..
integer, intent(out) :: info
! .. array Arguments ..
type(psbn_d_sparse_mat), intent(in), target :: a
type(psb_d_sparse_mat), intent(in), target :: a
type(psb_dprec_type), intent(inout) :: p
type(psb_desc_type), intent(in) :: desc_a
character, intent(in) :: upd
@ -48,7 +48,7 @@ subroutine psb_dbjac_bld(a,desc_a,p,upd,info)
integer :: int_err(5)
character :: trans, unitd
type(psb_dspmat_type) :: atmp
type(psbn_d_csr_sparse_mat), allocatable :: lf, uf
type(psb_d_csr_sparse_mat), allocatable :: lf, uf
real(psb_dpk_) :: t1,t2,t3,t4,t5,t6, t7, t8
integer nztota, err_act, n_row, nrow_a,n_col, nhalo
integer :: ictxt,np,me

@ -32,11 +32,11 @@
subroutine psb_ddiagsc_bld(a,desc_a,p,upd,info)
use psb_base_mod
use psbn_d_mat_mod
use psb_d_mat_mod
use psb_prec_mod, psb_protect_name => psb_ddiagsc_bld
Implicit None
type(psbn_d_sparse_mat), intent(in), target :: a
type(psb_d_sparse_mat), intent(in), target :: a
type(psb_desc_type), intent(in) :: desc_a
type(psb_dprec_type),intent(inout) :: p
character, intent(in) :: upd

@ -37,13 +37,13 @@ subroutine psb_dilu_fct(a,l,u,d,info,blck)
!
!
use psb_base_mod
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
! .. Scalar Arguments ..
integer, intent(out) :: info
! .. Array Arguments ..
type(psbn_d_sparse_mat),intent(in) :: a
type(psbn_d_csr_sparse_mat),intent(inout) :: l,u
type(psb_d_sparse_mat),intent(in) :: a
type(psb_d_csr_sparse_mat),intent(inout) :: l,u
type(psb_dspmat_type),intent(in), optional, target :: blck
real(psb_dpk_), intent(inout) :: d(:)
! .. Local Scalars ..
@ -124,11 +124,11 @@ subroutine psb_dilu_fct(a,l,u,d,info,blck)
contains
subroutine psb_dilu_fctint(m,ma,a,mb,b,&
& d,laspk,lia1,lia2,uaspk,uia1,uia2,l1,l2,info)
use psbn_d_base_mat_mod
use psb_d_base_mat_mod
implicit none
type(psbn_d_sparse_mat) :: a
type(psb_d_sparse_mat) :: a
type(psb_dspmat_type) :: b
integer :: m,ma,mb,l1,l2,info
integer, dimension(:) :: lia1,lia2,uia1,uia2
@ -137,7 +137,7 @@ contains
integer :: i,j,k,l,low1,low2,kk,jj,ll, irb, ktrw,err_act, nz
real(psb_dpk_) :: dia,temp
integer, parameter :: nrb=60
type(psbn_d_coo_sparse_mat) :: trw
type(psb_d_coo_sparse_mat) :: trw
integer, allocatable :: irow(:), icol(:)
real(psb_dpk_), allocatable :: val(:)

@ -32,11 +32,11 @@
subroutine psb_dprecbld(aa,desc_a,p,info,upd)
use psb_base_mod
use psbn_d_mat_mod
use psb_d_mat_mod
use psb_prec_mod, psb_protect_name => psb_dprecbld
Implicit None
type(psbn_d_sparse_mat), intent(in), target :: aa
type(psb_d_sparse_mat), intent(in), target :: aa
type(psb_desc_type), intent(in), target :: desc_a
type(psb_dprec_type),intent(inout) :: p
integer, intent(out) :: info

@ -45,11 +45,11 @@ module psb_prec_mod
character, intent(in),optional :: upd
end subroutine psb_sprecbld
subroutine psb_dprecbld(a,desc_a,prec,info,upd)
use psbn_d_mat_mod
use psb_d_mat_mod
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_type, only : psb_dprec_type
implicit none
type(psbn_d_sparse_mat), intent(in), target :: a
type(psb_d_sparse_mat), intent(in), target :: a
type(psb_desc_type), intent(in), target :: desc_a
type(psb_dprec_type), intent(inout) :: prec
integer, intent(out) :: info
@ -330,10 +330,10 @@ module psb_prec_mod
end subroutine psb_silu_fct
subroutine psb_dilu_fct(a,l,u,d,info,blck)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psbn_d_mat_mod
use psb_d_mat_mod
integer, intent(out) :: info
type(psbn_d_sparse_mat),intent(in) :: a
type(psbn_d_csr_sparse_mat),intent(inout) :: l,u
type(psb_d_sparse_mat),intent(in) :: a
type(psb_d_csr_sparse_mat),intent(inout) :: l,u
!!$ type(psb_dspmat_type),intent(in) :: a
!!$ type(psb_dspmat_type),intent(inout) :: l,u
type(psb_dspmat_type),intent(in), optional, target :: blck
@ -368,11 +368,11 @@ module psb_prec_mod
character, intent(in) :: upd
end subroutine psb_sbjac_bld
subroutine psb_dbjac_bld(a,desc_a,p,upd,info)
use psbn_d_mat_mod
use psb_d_mat_mod
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_type, only : psb_dprec_type
integer, intent(out) :: info
type(psbn_d_sparse_mat), intent(in), target :: a
type(psb_d_sparse_mat), intent(in), target :: a
type(psb_dprec_type), intent(inout) :: p
type(psb_desc_type), intent(in) :: desc_a
character, intent(in) :: upd
@ -410,9 +410,9 @@ module psb_prec_mod
subroutine psb_ddiagsc_bld(a,desc_a,p,upd,info)
use psb_base_mod, only : psb_desc_type, psb_dspmat_type, psb_dpk_
use psb_prec_type, only : psb_dprec_type
use psbn_d_mat_mod
use psb_d_mat_mod
integer, intent(out) :: info
type(psbn_d_sparse_mat), intent(in), target :: a
type(psb_d_sparse_mat), intent(in), target :: a
type(psb_dprec_type), intent(inout) :: p
type(psb_desc_type), intent(in) :: desc_a
character, intent(in) :: upd

@ -41,7 +41,7 @@ module psb_prec_type
& psb_dspmat_type, psb_zspmat_type, psb_dpk_, psb_spk_, psb_long_int_k_,&
& psb_desc_type, psb_sizeof, psb_sp_free, psb_cdfree,&
& psb_erractionsave, psb_erractionrestore, psb_error, psb_get_errstatus
use psbn_d_mat_mod, only : psbn_d_sparse_mat
use psb_d_mat_mod, only : psb_d_sparse_mat
integer, parameter :: psb_min_prec_=0, psb_noprec_=0, psb_diag_=1, &
& psb_bjac_=2, psb_max_prec_=2
@ -76,7 +76,7 @@ module psb_prec_type
end type psb_sprec_type
type psb_dprec_type
type(psbn_d_sparse_mat), allocatable :: av(:)
type(psb_d_sparse_mat), allocatable :: av(:)
real(psb_dpk_), allocatable :: d(:)
type(psb_desc_type) :: desc_data
integer, allocatable :: iprcparm(:)
@ -602,7 +602,7 @@ contains
function psb_dprec_sizeof(prec) result(val)
use psbn_d_mat_mod
use psb_d_mat_mod
type(psb_dprec_type), intent(in) :: prec
integer(psb_long_int_k_) :: val
integer :: i

@ -547,14 +547,14 @@ contains
! on exit : unchanged.
!
use psb_base_mod
use psbn_d_mat_mod
use psb_d_mat_mod
implicit none
! parameters
type(psb_dspmat_type) :: a_glob
real(psb_dpk_) :: b_glob(:)
integer :: ictxt
type(psbn_d_sparse_mat) :: a
type(psb_d_sparse_mat) :: a
real(psb_dpk_), allocatable :: b(:)
type(psb_desc_type) :: desc_a
integer, intent(out) :: info

Loading…
Cancel
Save