psblas-3.99

base/modules/Makefile
 base/modules/psb_cd_tools_mod.f90
 base/tools/psb_icdasb.F90
 util/psb_d_genpde_impl.f90
 util/psb_d_genpde_mod.f90
 util/psb_s_genpde_impl.f90
 util/psb_s_genpde_mod.f90

added MOLD to cdasb, called from genpde.
psblas-3.2.0
Salvatore Filippone 12 years ago
parent bdc3cc925a
commit adf1fea543

@ -61,9 +61,10 @@ psb_ip_reord_mod.o psi_serial_mod.o psb_sort_mod.o: $(BASIC_MODS)
psb_base_mat_mod.o: psi_serial_mod.o psb_base_mat_mod.o: psi_serial_mod.o
psb_s_base_mat_mod.o psb_d_base_mat_mod.o psb_c_base_mat_mod.o psb_z_base_mat_mod.o: psb_base_mat_mod.o psb_s_base_mat_mod.o psb_d_base_mat_mod.o psb_c_base_mat_mod.o psb_z_base_mat_mod.o: psb_base_mat_mod.o
psb_s_base_mat_mod.o: psb_s_base_vect_mod.o psb_s_base_mat_mod.o: psb_s_base_vect_mod.o
psb_d_base_mat_mod.o: psb_d_base_vect_mod.o psb_d_base_mat_mod.o: psb_d_base_vect_mod.o
psb_c_base_mat_mod.o: psb_c_base_vect_mod.o psb_c_base_mat_mod.o: psb_c_base_vect_mod.o
psb_z_base_mat_mod.o: psb_z_base_vect_mod.o psb_z_base_mat_mod.o: psb_z_base_vect_mod.o
psb_c_base_vect_mod.o psb_s_base_vect_mod.o psb_d_base_vect_mod.o psb_z_base_vect_mod.o: psb_i_base_vect_mod.o
psb_i_base_vect_mod.o psb_c_base_vect_mod.o psb_s_base_vect_mod.o psb_d_base_vect_mod.o psb_z_base_vect_mod.o: psi_serial_mod.o psb_realloc_mod.o psb_i_base_vect_mod.o psb_c_base_vect_mod.o psb_s_base_vect_mod.o psb_d_base_vect_mod.o psb_z_base_vect_mod.o: psi_serial_mod.o psb_realloc_mod.o
psb_s_mat_mod.o: psb_s_base_mat_mod.o psb_s_csr_mat_mod.o psb_s_csc_mat_mod.o psb_s_vect_mod.o psb_s_mat_mod.o: psb_s_base_mat_mod.o psb_s_csr_mat_mod.o psb_s_csc_mat_mod.o psb_s_vect_mod.o
psb_d_mat_mod.o: psb_d_base_mat_mod.o psb_d_csr_mat_mod.o psb_d_csc_mat_mod.o psb_d_vect_mod.o psb_d_mat_mod.o: psb_d_base_mat_mod.o psb_d_csr_mat_mod.o psb_d_csc_mat_mod.o psb_d_vect_mod.o

@ -149,7 +149,7 @@ module psb_cd_tools_mod
Type(psb_desc_type), intent(inout) :: desc Type(psb_desc_type), intent(inout) :: desc
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
logical, intent(in),optional :: ext_hv logical, intent(in),optional :: ext_hv
type(psb_i_base_vect_type), optional, intent(in) :: mold class(psb_i_base_vect_type), optional, intent(in) :: mold
end subroutine psb_icdasb end subroutine psb_icdasb
end interface end interface
@ -205,7 +205,7 @@ contains
Type(psb_desc_type), intent(inout) :: desc Type(psb_desc_type), intent(inout) :: desc
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
type(psb_i_base_vect_type), optional, intent(in) :: mold class(psb_i_base_vect_type), optional, intent(in) :: mold
call psb_icdasb(desc,info,ext_hv=.false.,mold=mold) call psb_icdasb(desc,info,ext_hv=.false.,mold=mold)
end subroutine psb_cdasb end subroutine psb_cdasb

@ -56,7 +56,7 @@ subroutine psb_icdasb(desc,info,ext_hv,mold)
type(psb_desc_type), intent(inout) :: desc type(psb_desc_type), intent(inout) :: desc
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
logical, intent(in), optional :: ext_hv logical, intent(in), optional :: ext_hv
type(psb_i_base_vect_type), optional, intent(in) :: mold class(psb_i_base_vect_type), optional, intent(in) :: mold
!....Locals.... !....Locals....
integer(psb_ipk_) :: int_err(5) integer(psb_ipk_) :: int_err(5)

@ -34,7 +34,7 @@
! the rhs. ! the rhs.
! !
subroutine psb_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& subroutine psb_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,&
& a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,nrl) & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl)
use psb_base_mod use psb_base_mod
use psb_d_genpde_mod, psb_protect_name => psb_d_gen_pde3d use psb_d_genpde_mod, psb_protect_name => psb_d_gen_pde3d
! !
@ -62,7 +62,8 @@ subroutine psb_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,&
character(len=*) :: afmt character(len=*) :: afmt
procedure(d_func_3d), optional :: f procedure(d_func_3d), optional :: f
class(psb_d_base_sparse_mat), optional :: amold class(psb_d_base_sparse_mat), optional :: amold
class(psb_d_base_vect_type), optional :: vmold class(psb_d_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
! Local variables. ! Local variables.
@ -285,7 +286,7 @@ subroutine psb_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,&
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()
call psb_cdasb(desc_a,info) call psb_cdasb(desc_a,info,mold=imold)
tcdasb = psb_wtime()-t1 tcdasb = psb_wtime()-t1
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()
@ -349,7 +350,7 @@ end subroutine psb_d_gen_pde3d
! the rhs. ! the rhs.
! !
subroutine psb_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& subroutine psb_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
& a1,a2,b1,b2,c,g,info,f,amold,vmold,nrl) & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,nrl)
use psb_base_mod use psb_base_mod
use psb_d_genpde_mod, psb_protect_name => psb_d_gen_pde2d use psb_d_genpde_mod, psb_protect_name => psb_d_gen_pde2d
! !
@ -378,6 +379,7 @@ subroutine psb_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
procedure(d_func_2d), optional :: f procedure(d_func_2d), optional :: f
class(psb_d_base_sparse_mat), optional :: amold class(psb_d_base_sparse_mat), optional :: amold
class(psb_d_base_vect_type), optional :: vmold class(psb_d_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
! Local variables. ! Local variables.
@ -575,7 +577,7 @@ subroutine psb_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()
call psb_cdasb(desc_a,info) call psb_cdasb(desc_a,info,mold=imold)
tcdasb = psb_wtime()-t1 tcdasb = psb_wtime()-t1
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()

@ -33,7 +33,7 @@ module psb_d_genpde_mod
use psb_base_mod, only : psb_dpk_, psb_ipk_, psb_desc_type,& use psb_base_mod, only : psb_dpk_, psb_ipk_, psb_desc_type,&
& psb_dspmat_type, psb_d_vect_type, dzero,& & psb_dspmat_type, psb_d_vect_type, dzero,&
& psb_d_base_sparse_mat, psb_d_base_vect_type & psb_d_base_sparse_mat, psb_d_base_vect_type, psb_i_base_vect_type
interface interface
function d_func_3d(x,y,z) result(val) function d_func_3d(x,y,z) result(val)
@ -45,7 +45,7 @@ module psb_d_genpde_mod
interface psb_gen_pde3d interface psb_gen_pde3d
subroutine psb_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt, & subroutine psb_d_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt, &
& a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,nrl) & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl)
! !
! Discretizes the partial differential equation ! Discretizes the partial differential equation
! !
@ -62,7 +62,7 @@ module psb_d_genpde_mod
! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation. ! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation.
! !
import :: psb_ipk_, psb_desc_type, psb_dspmat_type, psb_d_vect_type,& import :: psb_ipk_, psb_desc_type, psb_dspmat_type, psb_d_vect_type,&
& d_func_3d, psb_d_base_sparse_mat, psb_d_base_vect_type & d_func_3d, psb_d_base_sparse_mat, psb_d_base_vect_type, psb_i_base_vect_type
implicit none implicit none
procedure(d_func_3d) :: a1,a2,a3,c,b1,b2,b3,g procedure(d_func_3d) :: a1,a2,a3,c,b1,b2,b3,g
integer(psb_ipk_) :: idim integer(psb_ipk_) :: idim
@ -74,6 +74,7 @@ module psb_d_genpde_mod
procedure(d_func_3d), optional :: f procedure(d_func_3d), optional :: f
class(psb_d_base_sparse_mat), optional :: amold class(psb_d_base_sparse_mat), optional :: amold
class(psb_d_base_vect_type), optional :: vmold class(psb_d_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
end subroutine psb_d_gen_pde3d end subroutine psb_d_gen_pde3d
end interface end interface
@ -89,7 +90,7 @@ module psb_d_genpde_mod
interface psb_gen_pde2d interface psb_gen_pde2d
subroutine psb_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& subroutine psb_d_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
& a1,a2,b1,b2,c,g,info,f,amold,vmold,nrl) & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,nrl)
! !
! Discretizes the partial differential equation ! Discretizes the partial differential equation
! !
@ -106,7 +107,7 @@ module psb_d_genpde_mod
! Note that if b1=b2=c=0., the PDE is the Laplace equation. ! Note that if b1=b2=c=0., the PDE is the Laplace equation.
! !
import :: psb_ipk_, psb_desc_type, psb_dspmat_type, psb_d_vect_type,& import :: psb_ipk_, psb_desc_type, psb_dspmat_type, psb_d_vect_type,&
& d_func_2d, psb_d_base_sparse_mat, psb_d_base_vect_type & d_func_2d, psb_d_base_sparse_mat, psb_d_base_vect_type, psb_i_base_vect_type
implicit none implicit none
procedure(d_func_2d) :: a1,a2,c,b1,b2,g procedure(d_func_2d) :: a1,a2,c,b1,b2,g
integer(psb_ipk_) :: idim integer(psb_ipk_) :: idim
@ -118,6 +119,7 @@ module psb_d_genpde_mod
procedure(d_func_2d), optional :: f procedure(d_func_2d), optional :: f
class(psb_d_base_sparse_mat), optional :: amold class(psb_d_base_sparse_mat), optional :: amold
class(psb_d_base_vect_type), optional :: vmold class(psb_d_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
end subroutine psb_d_gen_pde2d end subroutine psb_d_gen_pde2d
end interface end interface

@ -34,7 +34,7 @@
! the rhs. ! the rhs.
! !
subroutine psb_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& subroutine psb_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,&
& a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,nrl) & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl)
use psb_base_mod use psb_base_mod
use psb_s_genpde_mod, psb_protect_name => psb_s_gen_pde3d use psb_s_genpde_mod, psb_protect_name => psb_s_gen_pde3d
! !
@ -63,6 +63,7 @@ subroutine psb_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,&
procedure(s_func_3d), optional :: f procedure(s_func_3d), optional :: f
class(psb_s_base_sparse_mat), optional :: amold class(psb_s_base_sparse_mat), optional :: amold
class(psb_s_base_vect_type), optional :: vmold class(psb_s_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
! Local variables. ! Local variables.
@ -285,7 +286,7 @@ subroutine psb_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,&
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()
call psb_cdasb(desc_a,info) call psb_cdasb(desc_a,info,mold=imold)
tcdasb = psb_wtime()-t1 tcdasb = psb_wtime()-t1
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()
@ -349,7 +350,7 @@ end subroutine psb_s_gen_pde3d
! the rhs. ! the rhs.
! !
subroutine psb_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& subroutine psb_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
& a1,a2,b1,b2,c,g,info,f,amold,vmold,nrl) & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,nrl)
use psb_base_mod use psb_base_mod
use psb_s_genpde_mod, psb_protect_name => psb_s_gen_pde2d use psb_s_genpde_mod, psb_protect_name => psb_s_gen_pde2d
! !
@ -378,6 +379,7 @@ subroutine psb_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
procedure(s_func_2d), optional :: f procedure(s_func_2d), optional :: f
class(psb_s_base_sparse_mat), optional :: amold class(psb_s_base_sparse_mat), optional :: amold
class(psb_s_base_vect_type), optional :: vmold class(psb_s_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
! Local variables. ! Local variables.
@ -575,7 +577,7 @@ subroutine psb_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()
call psb_cdasb(desc_a,info) call psb_cdasb(desc_a,info,mold=imold)
tcdasb = psb_wtime()-t1 tcdasb = psb_wtime()-t1
call psb_barrier(ictxt) call psb_barrier(ictxt)
t1 = psb_wtime() t1 = psb_wtime()

@ -33,7 +33,7 @@ module psb_s_genpde_mod
use psb_base_mod, only : psb_spk_, psb_ipk_, psb_desc_type,& use psb_base_mod, only : psb_spk_, psb_ipk_, psb_desc_type,&
& psb_sspmat_type, psb_s_vect_type, szero,& & psb_sspmat_type, psb_s_vect_type, szero,&
& psb_s_base_sparse_mat, psb_s_base_vect_type & psb_s_base_sparse_mat, psb_s_base_vect_type, psb_i_base_vect_type
interface interface
function s_func_3d(x,y,z) result(val) function s_func_3d(x,y,z) result(val)
@ -45,7 +45,7 @@ module psb_s_genpde_mod
interface psb_gen_pde3d interface psb_gen_pde3d
subroutine psb_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,& subroutine psb_s_gen_pde3d(ictxt,idim,a,bv,xv,desc_a,afmt,&
& a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,nrl) & a1,a2,a3,b1,b2,b3,c,g,info,f,amold,vmold,imold,nrl)
! !
! Discretizes the partial differential equation ! Discretizes the partial differential equation
! !
@ -62,7 +62,7 @@ module psb_s_genpde_mod
! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation. ! Note that if b1=b2=b3=c=0., the PDE is the Laplace equation.
! !
import :: psb_ipk_, psb_desc_type, psb_sspmat_type, psb_s_vect_type, & import :: psb_ipk_, psb_desc_type, psb_sspmat_type, psb_s_vect_type, &
& s_func_3d, psb_s_base_sparse_mat, psb_s_base_vect_type & s_func_3d, psb_s_base_sparse_mat, psb_s_base_vect_type, psb_i_base_vect_type
implicit none implicit none
procedure(s_func_3d) :: a1,a2,a3,c,b1,b2,b3,g procedure(s_func_3d) :: a1,a2,a3,c,b1,b2,b3,g
integer(psb_ipk_) :: idim integer(psb_ipk_) :: idim
@ -74,6 +74,7 @@ module psb_s_genpde_mod
procedure(s_func_3d), optional :: f procedure(s_func_3d), optional :: f
class(psb_s_base_sparse_mat), optional :: amold class(psb_s_base_sparse_mat), optional :: amold
class(psb_s_base_vect_type), optional :: vmold class(psb_s_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
end subroutine psb_s_gen_pde3d end subroutine psb_s_gen_pde3d
end interface end interface
@ -89,7 +90,7 @@ module psb_s_genpde_mod
interface psb_gen_pde2d interface psb_gen_pde2d
subroutine psb_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,& subroutine psb_s_gen_pde2d(ictxt,idim,a,bv,xv,desc_a,afmt,&
& a1,a2,b1,b2,c,g,info,f,amold,vmold,nrl) & a1,a2,b1,b2,c,g,info,f,amold,vmold,imold,nrl)
! !
! Discretizes the partial differential equation ! Discretizes the partial differential equation
! !
@ -106,7 +107,7 @@ module psb_s_genpde_mod
! Note that if b1=b2=c=0., the PDE is the Laplace equation. ! Note that if b1=b2=c=0., the PDE is the Laplace equation.
! !
import :: psb_ipk_, psb_desc_type, psb_sspmat_type, psb_s_vect_type,& import :: psb_ipk_, psb_desc_type, psb_sspmat_type, psb_s_vect_type,&
& s_func_2d, psb_s_base_sparse_mat, psb_s_base_vect_type & s_func_2d, psb_s_base_sparse_mat, psb_s_base_vect_type, psb_i_base_vect_type
implicit none implicit none
procedure(s_func_2d) :: a1,a2,c,b1,b2,g procedure(s_func_2d) :: a1,a2,c,b1,b2,g
integer(psb_ipk_) :: idim integer(psb_ipk_) :: idim
@ -118,6 +119,7 @@ module psb_s_genpde_mod
procedure(s_func_2d), optional :: f procedure(s_func_2d), optional :: f
class(psb_s_base_sparse_mat), optional :: amold class(psb_s_base_sparse_mat), optional :: amold
class(psb_s_base_vect_type), optional :: vmold class(psb_s_base_vect_type), optional :: vmold
class(psb_i_base_vect_type), optional :: imold
integer(psb_ipk_), optional :: nrl integer(psb_ipk_), optional :: nrl
end subroutine psb_s_gen_pde2d end subroutine psb_s_gen_pde2d
end interface end interface

Loading…
Cancel
Save