base/modules/psb_c_base_vect_mod.f90
 base/modules/psb_c_mat_mod.f90
 base/modules/psb_c_vect_mod.f90
 base/modules/psb_d_base_vect_mod.f90
 base/modules/psb_d_mat_mod.f90
 base/modules/psb_d_vect_mod.f90
 base/modules/psb_desc_type.f90
 base/modules/psb_s_base_vect_mod.f90
 base/modules/psb_s_mat_mod.f90
 base/modules/psb_s_vect_mod.f90
 base/modules/psb_z_base_vect_mod.f90
 base/modules/psb_z_mat_mod.f90
 base/modules/psb_z_vect_mod.f90
 base/serial/impl/psb_c_mat_impl.F90
 base/serial/impl/psb_d_mat_impl.F90
 base/serial/impl/psb_s_mat_impl.F90
 base/serial/impl/psb_z_mat_impl.F90
 base/tools/psb_d_map.f90
 test/pargen/ppde.f90


VECT: fixed behaviour of set_vect.
MAT:  fixed interface of CP_TO.
psblas3-type-indexed
Salvatore Filippone 13 years ago
parent f07faa91c4
commit cd47d999ba

@ -113,10 +113,14 @@ contains
subroutine c_base_set_vect(x,val)
class(psb_c_base_vect_type), intent(inout) :: x
complex(psb_spk_), intent(in) :: val(:)
integer :: nr
integer :: info
if (allocated(x%v)) then
nr = min(size(x%v),size(val))
x%v(1:nr) = val(1:nr)
else
x%v = val
end if
end subroutine c_base_set_vect

@ -491,7 +491,7 @@ module psb_c_mat_mod
subroutine psb_c_cp_from(a,b)
import :: psb_cspmat_type, psb_spk_, psb_c_base_sparse_mat
class(psb_cspmat_type), intent(out) :: a
class(psb_c_base_sparse_mat), intent(inout), allocatable :: b
class(psb_c_base_sparse_mat), intent(in) :: b
end subroutine psb_c_cp_from
end interface

@ -113,10 +113,14 @@ contains
subroutine d_base_set_vect(x,val)
class(psb_d_base_vect_type), intent(inout) :: x
real(psb_dpk_), intent(in) :: val(:)
integer :: nr
integer :: info
if (allocated(x%v)) then
nr = min(size(x%v),size(val))
x%v(1:nr) = val(1:nr)
else
x%v = val
end if
end subroutine d_base_set_vect

@ -493,7 +493,7 @@ module psb_d_mat_mod
subroutine psb_d_cp_from(a,b)
import :: psb_dspmat_type, psb_dpk_, psb_d_base_sparse_mat
class(psb_dspmat_type), intent(out) :: a
class(psb_d_base_sparse_mat), intent(inout), allocatable :: b
class(psb_d_base_sparse_mat), intent(in) :: b
end subroutine psb_d_cp_from
end interface

@ -224,37 +224,13 @@ module psb_descriptor_type
procedure, pass(desc) :: get_local_cols => psb_cd_get_local_cols
procedure, pass(desc) :: get_global_rows => psb_cd_get_global_rows
procedure, pass(desc) :: get_global_cols => psb_cd_get_global_cols
procedure, pass(desc) :: sizeof => psb_cd_sizeof
end type psb_desc_type
interface psb_sizeof
module procedure psb_cd_sizeof
end interface psb_sizeof
!!$ interface psb_is_ok_desc
!!$ module procedure psb_is_ok_desc
!!$ end interface psb_is_ok_desc
!!$
!!$ interface psb_is_valid_desc
!!$ module procedure psb_is_valid_desc
!!$ end interface psb_is_valid_desc
!!$
!!$ interface psb_is_asb_desc
!!$ module procedure psb_is_asb_desc
!!$ end interface psb_is_asb_desc
!!$
!!$ interface psb_is_upd_desc
!!$ module procedure psb_is_upd_desc
!!$ end interface psb_is_upd_desc
!!$
!!$ interface psb_is_ovl_desc
!!$ module procedure psb_is_ovl_desc
!!$ end interface psb_is_ovl_desc
!!$
!!$ interface psb_is_bld_desc
!!$ module procedure psb_is_bld_desc
!!$ end interface psb_is_bld_desc
!!$
interface psb_move_alloc
module procedure psb_cdtransfer
end interface psb_move_alloc
@ -273,7 +249,7 @@ contains
implicit none
!....Parameters...
Type(psb_desc_type), intent(in) :: desc
class(psb_desc_type), intent(in) :: desc
integer(psb_long_int_k_) :: val
val = 0

@ -113,10 +113,14 @@ contains
subroutine s_base_set_vect(x,val)
class(psb_s_base_vect_type), intent(inout) :: x
real(psb_spk_), intent(in) :: val(:)
integer :: nr
integer :: info
if (allocated(x%v)) then
nr = min(size(x%v),size(val))
x%v(1:nr) = val(1:nr)
else
x%v = val
end if
end subroutine s_base_set_vect

@ -494,7 +494,7 @@ module psb_s_mat_mod
subroutine psb_s_cp_from(a,b)
import :: psb_sspmat_type, psb_spk_, psb_s_base_sparse_mat
class(psb_sspmat_type), intent(out) :: a
class(psb_s_base_sparse_mat), intent(inout), allocatable :: b
class(psb_s_base_sparse_mat), intent(in) :: b
end subroutine psb_s_cp_from
end interface

@ -113,13 +113,18 @@ contains
subroutine z_base_set_vect(x,val)
class(psb_z_base_vect_type), intent(inout) :: x
complex(psb_dpk_), intent(in) :: val(:)
integer :: nr
integer :: info
if (allocated(x%v)) then
nr = min(size(x%v),size(val))
x%v(1:nr) = val(1:nr)
else
x%v = val
end if
end subroutine z_base_set_vect
function constructor(x) result(this)
complex(psb_dpk_) :: x(:)
type(psb_z_base_vect_type) :: this

@ -491,7 +491,7 @@ module psb_z_mat_mod
subroutine psb_z_cp_from(a,b)
import :: psb_zspmat_type, psb_dpk_, psb_z_base_sparse_mat
class(psb_zspmat_type), intent(out) :: a
class(psb_z_base_sparse_mat), intent(inout), allocatable :: b
class(psb_z_base_sparse_mat), intent(in) :: b
end subroutine psb_z_cp_from
end interface

@ -1414,7 +1414,7 @@ subroutine psb_c_cp_from(a,b)
use psb_c_mat_mod, psb_protect_name => psb_c_cp_from
implicit none
class(psb_cspmat_type), intent(out) :: a
class(psb_c_base_sparse_mat), intent(inout), allocatable :: b
class(psb_c_base_sparse_mat), intent(in) :: b
Integer :: err_act, info
character(len=20) :: name='clone'
logical, parameter :: debug=.false.

@ -1415,7 +1415,7 @@ subroutine psb_d_cp_from(a,b)
use psb_d_mat_mod, psb_protect_name => psb_d_cp_from
implicit none
class(psb_dspmat_type), intent(out) :: a
class(psb_d_base_sparse_mat), intent(inout), allocatable :: b
class(psb_d_base_sparse_mat), intent(in) :: b
Integer :: err_act, info
character(len=20) :: name='clone'
logical, parameter :: debug=.false.

@ -1413,7 +1413,7 @@ subroutine psb_s_cp_from(a,b)
use psb_s_mat_mod, psb_protect_name => psb_s_cp_from
implicit none
class(psb_sspmat_type), intent(out) :: a
class(psb_s_base_sparse_mat), intent(inout), allocatable :: b
class(psb_s_base_sparse_mat), intent(in) :: b
Integer :: err_act, info
character(len=20) :: name='clone'
logical, parameter :: debug=.false.

@ -1414,7 +1414,7 @@ subroutine psb_z_cp_from(a,b)
use psb_z_mat_mod, psb_protect_name => psb_z_cp_from
implicit none
class(psb_zspmat_type), intent(out) :: a
class(psb_z_base_sparse_mat), intent(inout), allocatable :: b
class(psb_z_base_sparse_mat), intent(in) :: b
Integer :: err_act, info
character(len=20) :: name='clone'
logical, parameter :: debug=.false.

@ -562,7 +562,10 @@ contains
element = element+1
endif
! term depending on (x+1,y,z)
if (ix<idim) then
if (ix==idim) then
val(element)=-b3(x,y,z)/deltah2
zt(k) = exp(-y**2-z**2)*exp(-x)*(-val(element))
else
val(element)=-b3(x,y,z)/deltah2
icol(element) = (ix)*idim*idim+(iy-1)*idim+(iz)
irow(element) = glob_row

Loading…
Cancel
Save