psblas-submodules:

base/internals/psi_cswapdata.F90
 base/internals/psi_cswaptran.F90
 base/internals/psi_dswapdata.F90
 base/internals/psi_dswaptran.F90
 base/internals/psi_iswapdata.F90
 base/internals/psi_iswaptran.F90
 base/internals/psi_sswapdata.F90
 base/internals/psi_sswaptran.F90
 base/internals/psi_zswapdata.F90
 base/internals/psi_zswaptran.F90
 base/modules/psb_c_csr_mat_mod.f90
 base/modules/psb_d_csr_mat_mod.f90
 base/modules/psb_s_csr_mat_mod.f90
 base/modules/psb_z_csr_mat_mod.f90
 base/modules/psi_c_mod.f90
 base/modules/psi_d_mod.f90
 base/modules/psi_i_mod.f90
 base/modules/psi_s_mod.f90
 base/modules/psi_z_mod.f90

interface/implementation  mismatch fixes
psblas3-submodules
Salvatore Filippone 10 years ago
parent 7e5d678161
commit d53fd1392b

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

@ -86,8 +86,9 @@
submodule (psi_d_mod) psi_dswapdata_mod
contains
subroutine psi_dswapdatam(flag,n,beta,y,desc_a,work,info,data)
use psb_error_mod
use psb_desc_mod
use psb_penv_mod
@ -156,7 +157,7 @@ contains
subroutine psi_dswapidxm(ictxt,icomm,flag,n,beta,y,idx, &
& totxch,totsnd,totrcv,work,info)
use psi_serial_mod
use psb_error_mod
use psb_desc_mod
use psb_penv_mod
@ -657,7 +658,7 @@ contains
!
subroutine psi_dswapidxv(ictxt,icomm,flag,beta,y,idx, &
& totxch,totsnd,totrcv,work,info)
use psi_serial_mod
use psb_error_mod
use psb_desc_mod
use psb_penv_mod
@ -1111,7 +1112,6 @@ contains
use psb_desc_mod
use psb_penv_mod
use psb_d_base_vect_mod
use psi_serial_mod
#ifdef MPI_MOD
use mpi
#endif

@ -160,7 +160,7 @@ contains
end subroutine psi_dswaptranm
subroutine psi_dtranidxm(ictxt,icomm,flag,n,beta,y,idx,totxch,totsnd,totrcv,work,info)
use psi_serial_mod
use psb_error_mod
use psb_desc_mod
use psb_penv_mod
@ -661,7 +661,6 @@ contains
subroutine psi_dtranidxv(ictxt,icomm,flag,beta,y,idx,totxch,totsnd,totrcv,work,info)
use psi_serial_mod
use psb_error_mod
use psb_desc_mod
use psb_penv_mod
@ -1127,7 +1126,7 @@ contains
!
subroutine psi_dtran_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
use psi_serial_mod
use psb_error_mod
use psb_desc_mod
use psb_penv_mod
@ -1164,7 +1163,7 @@ contains
info=psb_success_
name='psi_swap_tran'
call psb_erractionsave(err_act)
iictxt = ictxt
iictxt = ictxt
iicomm = icomm
call psb_info(iictxt,me,np)

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

@ -98,12 +98,17 @@ module psb_c_csr_mat_mod
procedure, pass(a) :: print => psb_c_csr_print
procedure, pass(a) :: free => c_csr_free
procedure, pass(a) :: mold => psb_c_csr_mold
procedure, pass(a) :: get_irpp => c_csr_get_irpp
procedure, pass(a) :: get_jap => c_csr_get_jap
procedure, pass(a) :: get_valp => c_csr_get_valp
end type psb_c_csr_sparse_mat
private :: c_csr_get_nzeros, c_csr_free, c_csr_get_fmt, &
& c_csr_get_size, c_csr_sizeof, c_csr_get_nz_row, &
& c_csr_is_by_rows
& c_csr_is_by_rows, c_csr_get_irpp, c_csr_get_jap, &
& c_csr_get_valp
!> \memberof psb_c_csr_sparse_mat
!| \see psb_base_mat_mod::psb_base_reallocate_nz
@ -579,6 +584,45 @@ contains
return
end subroutine c_csr_free
function c_csr_get_irpp(a) result(res)
implicit none
class(psb_c_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%irp)) then
res => a%irp
else
res => null()
end if
end function c_csr_get_irpp
function c_csr_get_jap(a) result(res)
implicit none
class(psb_c_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%ja)) then
res => a%ja
else
res => null()
end if
end function c_csr_get_jap
function c_csr_get_valp(a) result(res)
implicit none
class(psb_c_csr_sparse_mat), intent(in), target :: a
complex(psb_spk_), pointer :: res(:)
if (allocated(a%val)) then
res => a%val
else
res => null()
end if
end function c_csr_get_valp
end module psb_c_csr_mat_mod

@ -98,12 +98,17 @@ module psb_d_csr_mat_mod
procedure, pass(a) :: print => psb_d_csr_print
procedure, pass(a) :: free => d_csr_free
procedure, pass(a) :: mold => psb_d_csr_mold
procedure, pass(a) :: get_irpp => d_csr_get_irpp
procedure, pass(a) :: get_jap => d_csr_get_jap
procedure, pass(a) :: get_valp => d_csr_get_valp
end type psb_d_csr_sparse_mat
private :: d_csr_get_nzeros, d_csr_free, d_csr_get_fmt, &
& d_csr_get_size, d_csr_sizeof, d_csr_get_nz_row, &
& d_csr_is_by_rows
& d_csr_is_by_rows, d_csr_get_irpp, d_csr_get_jap, &
& d_csr_get_valp
!> \memberof psb_d_csr_sparse_mat
!| \see psb_base_mat_mod::psb_base_reallocate_nz
@ -579,6 +584,45 @@ contains
return
end subroutine d_csr_free
function d_csr_get_irpp(a) result(res)
implicit none
class(psb_d_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%irp)) then
res => a%irp
else
res => null()
end if
end function d_csr_get_irpp
function d_csr_get_jap(a) result(res)
implicit none
class(psb_d_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%ja)) then
res => a%ja
else
res => null()
end if
end function d_csr_get_jap
function d_csr_get_valp(a) result(res)
implicit none
class(psb_d_csr_sparse_mat), intent(in), target :: a
real(psb_dpk_), pointer :: res(:)
if (allocated(a%val)) then
res => a%val
else
res => null()
end if
end function d_csr_get_valp
end module psb_d_csr_mat_mod

@ -98,12 +98,17 @@ module psb_s_csr_mat_mod
procedure, pass(a) :: print => psb_s_csr_print
procedure, pass(a) :: free => s_csr_free
procedure, pass(a) :: mold => psb_s_csr_mold
procedure, pass(a) :: get_irpp => s_csr_get_irpp
procedure, pass(a) :: get_jap => s_csr_get_jap
procedure, pass(a) :: get_valp => s_csr_get_valp
end type psb_s_csr_sparse_mat
private :: s_csr_get_nzeros, s_csr_free, s_csr_get_fmt, &
& s_csr_get_size, s_csr_sizeof, s_csr_get_nz_row, &
& s_csr_is_by_rows
& s_csr_is_by_rows, s_csr_get_irpp, s_csr_get_jap, &
& s_csr_get_valp
!> \memberof psb_s_csr_sparse_mat
!| \see psb_base_mat_mod::psb_base_reallocate_nz
@ -579,6 +584,45 @@ contains
return
end subroutine s_csr_free
function s_csr_get_irpp(a) result(res)
implicit none
class(psb_s_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%irp)) then
res => a%irp
else
res => null()
end if
end function s_csr_get_irpp
function s_csr_get_jap(a) result(res)
implicit none
class(psb_s_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%ja)) then
res => a%ja
else
res => null()
end if
end function s_csr_get_jap
function s_csr_get_valp(a) result(res)
implicit none
class(psb_s_csr_sparse_mat), intent(in), target :: a
real(psb_spk_), pointer :: res(:)
if (allocated(a%val)) then
res => a%val
else
res => null()
end if
end function s_csr_get_valp
end module psb_s_csr_mat_mod

@ -98,12 +98,17 @@ module psb_z_csr_mat_mod
procedure, pass(a) :: print => psb_z_csr_print
procedure, pass(a) :: free => z_csr_free
procedure, pass(a) :: mold => psb_z_csr_mold
procedure, pass(a) :: get_irpp => z_csr_get_irpp
procedure, pass(a) :: get_jap => z_csr_get_jap
procedure, pass(a) :: get_valp => z_csr_get_valp
end type psb_z_csr_sparse_mat
private :: z_csr_get_nzeros, z_csr_free, z_csr_get_fmt, &
& z_csr_get_size, z_csr_sizeof, z_csr_get_nz_row, &
& z_csr_is_by_rows
& z_csr_is_by_rows, z_csr_get_irpp, z_csr_get_jap, &
& z_csr_get_valp
!> \memberof psb_z_csr_sparse_mat
!| \see psb_base_mat_mod::psb_base_reallocate_nz
@ -579,6 +584,45 @@ contains
return
end subroutine z_csr_free
function z_csr_get_irpp(a) result(res)
implicit none
class(psb_z_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%irp)) then
res => a%irp
else
res => null()
end if
end function z_csr_get_irpp
function z_csr_get_jap(a) result(res)
implicit none
class(psb_z_csr_sparse_mat), intent(in), target :: a
integer(psb_ipk_), pointer :: res(:)
if (allocated(a%ja)) then
res => a%ja
else
res => null()
end if
end function z_csr_get_jap
function z_csr_get_valp(a) result(res)
implicit none
class(psb_z_csr_sparse_mat), intent(in), target :: a
complex(psb_dpk_), pointer :: res(:)
if (allocated(a%val)) then
res => a%val
else
res => null()
end if
end function z_csr_get_valp
end module psb_z_csr_mat_mod

@ -76,9 +76,9 @@ module psi_c_mod
complex(psb_spk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_cswapidxv
module subroutine psi_cswap_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_cswap_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_c_base_vect_type) :: y
complex(psb_spk_) :: beta
@ -131,9 +131,9 @@ module psi_c_mod
complex(psb_spk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_ctranidxv
module subroutine psi_ctran_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_ctran_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_c_base_vect_type) :: y
complex(psb_spk_) :: beta

@ -76,9 +76,9 @@ module psi_d_mod
real(psb_dpk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_dswapidxv
module subroutine psi_dswap_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_dswap_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_d_base_vect_type) :: y
real(psb_dpk_) :: beta
@ -131,9 +131,9 @@ module psi_d_mod
real(psb_dpk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_dtranidxv
module subroutine psi_dtran_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_dtran_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_d_base_vect_type) :: y
real(psb_dpk_) :: beta

@ -218,9 +218,9 @@ module psi_i_mod
integer(psb_ipk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_iswapidxv
module subroutine psi_iswap_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_iswap_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_i_base_vect_type) :: y
integer(psb_ipk_) :: beta
@ -273,9 +273,9 @@ module psi_i_mod
integer(psb_ipk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_itranidxv
module subroutine psi_itran_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_itran_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_i_base_vect_type) :: y
integer(psb_ipk_) :: beta

@ -76,9 +76,9 @@ module psi_s_mod
real(psb_spk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_sswapidxv
module subroutine psi_sswap_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_sswap_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_s_base_vect_type) :: y
real(psb_spk_) :: beta
@ -131,9 +131,9 @@ module psi_s_mod
real(psb_spk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_stranidxv
module subroutine psi_stran_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_stran_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_s_base_vect_type) :: y
real(psb_spk_) :: beta

@ -76,9 +76,9 @@ module psi_z_mod
complex(psb_dpk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_zswapidxv
module subroutine psi_zswap_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_zswap_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_z_base_vect_type) :: y
complex(psb_dpk_) :: beta
@ -131,9 +131,9 @@ module psi_z_mod
complex(psb_dpk_),target :: work(:)
integer(psb_ipk_), intent(in) :: idx(:),totxch,totsnd,totrcv
end subroutine psi_ztranidxv
module subroutine psi_ztran_vidx_vect(iictxt,iicomm,flag,beta,y,idx,&
module subroutine psi_ztran_vidx_vect(ictxt,icomm,flag,beta,y,idx,&
& totxch,totsnd,totrcv,work,info)
integer(psb_ipk_), intent(in) :: iictxt,iicomm,flag
integer(psb_ipk_), intent(in) :: ictxt,icomm,flag
integer(psb_ipk_), intent(out) :: info
class(psb_z_base_vect_type) :: y
complex(psb_dpk_) :: beta

Loading…
Cancel
Save