test/serial/Makefile
 test/serial/d_matgen.F90
 test/serial/psb_d_cxx_impl.f90
 test/serial/psb_d_cxx_mat_mod.f90
 test/serial/psb_d_xyz_impl.f90
 test/serial/psb_d_xyz_mat_mod.f90

Use XYZ instead of CXX, was confusing. 
New error handling.
psblas3-accel
Salvatore Filippone 10 years ago
parent b9ab03266e
commit ca4a919959

@ -16,10 +16,10 @@ EXEDIR=./runs
all: d_matgen all: d_matgen
psb_d_cxx_impl.o d_matgen.o: psb_d_cxx_mat_mod.o psb_d_xyz_impl.o d_matgen.o: psb_d_xyz_mat_mod.o
d_matgen: d_matgen.o psb_d_cxx_mat_mod.o psb_d_cxx_impl.o d_matgen: d_matgen.o psb_d_xyz_mat_mod.o psb_d_xyz_impl.o
$(F90LINK) $(LINKOPT) d_matgen.o psb_d_cxx_mat_mod.o psb_d_cxx_impl.o \ $(F90LINK) $(LINKOPT) d_matgen.o psb_d_xyz_mat_mod.o psb_d_xyz_impl.o \
-o d_matgen $(PSBLAS_LIB) $(LDLIBS) -o d_matgen $(PSBLAS_LIB) $(LDLIBS)
/bin/cp -p $(CPUPDFLAG) d_matgen $(EXEDIR) /bin/cp -p $(CPUPDFLAG) d_matgen $(EXEDIR)
# /bin/mv d_matgen $(EXEDIR) # /bin/mv d_matgen $(EXEDIR)
@ -29,7 +29,7 @@ check: all
clean: clean:
/bin/rm -f d_matgen.o \ /bin/rm -f d_matgen.o \
psb_d_cxx_mat_mod.o psb_d_cxx_impl.o *$(.mod) psb_d_xyz_mat_mod.o psb_d_xyz_impl.o *$(.mod)
verycleanlib: verycleanlib:
(cd ../..; make veryclean) (cd ../..; make veryclean)
lib: lib:

@ -2,7 +2,7 @@
program d_matgen program d_matgen
use psb_base_mod use psb_base_mod
use psb_util_mod use psb_util_mod
use psb_d_cxx_mat_mod use psb_d_xyz_mat_mod
implicit none implicit none
! input parameters ! input parameters
@ -29,7 +29,7 @@ program d_matgen
integer(psb_long_int_k_) :: amatsize, precsize, descsize integer(psb_long_int_k_) :: amatsize, precsize, descsize
real(psb_dpk_) :: err, eps real(psb_dpk_) :: err, eps
type(psb_d_csr_sparse_mat) :: acsr type(psb_d_csr_sparse_mat) :: acsr
type(psb_d_cxx_sparse_mat) :: acxx type(psb_d_xyz_sparse_mat) :: axyz
! other variables ! other variables
integer(psb_ipk_) :: info, err_act integer(psb_ipk_) :: info, err_act
@ -64,7 +64,7 @@ program d_matgen
& a1,a2,a3,b1,b2,b3,c,g,info,amold=acsr) & a1,a2,a3,b1,b2,b3,c,g,info,amold=acsr)
else if (.false.) then else if (.false.) then
call psb_gen_pde3d(ictxt,idim,a,b,x,desc_a,afmt,& call psb_gen_pde3d(ictxt,idim,a,b,x,desc_a,afmt,&
& a1,a2,a3,b1,b2,b3,c,g,info,amold=acxx) & a1,a2,a3,b1,b2,b3,c,g,info,amold=axyz)
end if end if

@ -43,12 +43,12 @@
! !
! == =================================== ! == ===================================
subroutine psb_d_cxx_csmv(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_csmv(alpha,a,x,beta,y,info,trans)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csmv use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csmv
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:) real(psb_dpk_), intent(in) :: alpha, beta, x(:)
real(psb_dpk_), intent(inout) :: y(:) real(psb_dpk_), intent(inout) :: y(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -60,7 +60,7 @@ subroutine psb_d_cxx_csmv(alpha,a,x,beta,y,info,trans)
logical :: tra, ctra logical :: tra, ctra
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_csmv' character(len=20) :: name='d_xyz_csmv'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -105,7 +105,7 @@ subroutine psb_d_cxx_csmv(alpha,a,x,beta,y,info,trans)
end if end if
call psb_d_cxx_csmv_inner(m,n,alpha,a%irp,a%ja,a%val,& call psb_d_xyz_csmv_inner(m,n,alpha,a%irp,a%ja,a%val,&
& a%is_triangle(),a%is_unit(),& & a%is_triangle(),a%is_unit(),&
& x,beta,y,tra,ctra) & x,beta,y,tra,ctra)
@ -116,7 +116,7 @@ subroutine psb_d_cxx_csmv(alpha,a,x,beta,y,info,trans)
return return
contains contains
subroutine psb_d_cxx_csmv_inner(m,n,alpha,irp,ja,val,is_triangle,is_unit,& subroutine psb_d_xyz_csmv_inner(m,n,alpha,irp,ja,val,is_triangle,is_unit,&
& x,beta,y,tra,ctra) & x,beta,y,tra,ctra)
integer(psb_ipk_), intent(in) :: m,n,irp(*),ja(*) integer(psb_ipk_), intent(in) :: m,n,irp(*),ja(*)
real(psb_dpk_), intent(in) :: alpha, beta, x(*),val(*) real(psb_dpk_), intent(in) :: alpha, beta, x(*),val(*)
@ -381,17 +381,17 @@ contains
end if end if
end subroutine psb_d_cxx_csmv_inner end subroutine psb_d_xyz_csmv_inner
end subroutine psb_d_cxx_csmv end subroutine psb_d_xyz_csmv
subroutine psb_d_cxx_csmm(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_csmm(alpha,a,x,beta,y,info,trans)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csmm use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csmm
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:,:) real(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
real(psb_dpk_), intent(inout) :: y(:,:) real(psb_dpk_), intent(inout) :: y(:,:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -403,7 +403,7 @@ subroutine psb_d_cxx_csmm(alpha,a,x,beta,y,info,trans)
logical :: tra, ctra logical :: tra, ctra
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_csmm' character(len=20) :: name='d_xyz_csmm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
info = psb_success_ info = psb_success_
@ -454,7 +454,7 @@ subroutine psb_d_cxx_csmm(alpha,a,x,beta,y,info,trans)
goto 9999 goto 9999
end if end if
call psb_d_cxx_csmm_inner(m,n,nc,alpha,a%irp,a%ja,a%val, & call psb_d_xyz_csmm_inner(m,n,nc,alpha,a%irp,a%ja,a%val, &
& a%is_triangle(),a%is_unit(),x,size(x,1,kind=psb_ipk_), & & a%is_triangle(),a%is_unit(),x,size(x,1,kind=psb_ipk_), &
& beta,y,size(y,1,kind=psb_ipk_),tra,ctra,acc) & beta,y,size(y,1,kind=psb_ipk_),tra,ctra,acc)
@ -465,7 +465,7 @@ subroutine psb_d_cxx_csmm(alpha,a,x,beta,y,info,trans)
return return
contains contains
subroutine psb_d_cxx_csmm_inner(m,n,nc,alpha,irp,ja,val,& subroutine psb_d_xyz_csmm_inner(m,n,nc,alpha,irp,ja,val,&
& is_triangle,is_unit,x,ldx,beta,y,ldy,tra,ctra,acc) & is_triangle,is_unit,x,ldx,beta,y,ldy,tra,ctra,acc)
integer(psb_ipk_), intent(in) :: m,n,ldx,ldy,nc,irp(*),ja(*) integer(psb_ipk_), intent(in) :: m,n,ldx,ldy,nc,irp(*),ja(*)
real(psb_dpk_), intent(in) :: alpha, beta, x(ldx,*),val(*) real(psb_dpk_), intent(in) :: alpha, beta, x(ldx,*),val(*)
@ -727,17 +727,17 @@ contains
end do end do
end if end if
end subroutine psb_d_cxx_csmm_inner end subroutine psb_d_xyz_csmm_inner
end subroutine psb_d_cxx_csmm end subroutine psb_d_xyz_csmm
subroutine psb_d_cxx_cssv(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_cssv(alpha,a,x,beta,y,info,trans)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_cssv use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_cssv
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:) real(psb_dpk_), intent(in) :: alpha, beta, x(:)
real(psb_dpk_), intent(inout) :: y(:) real(psb_dpk_), intent(inout) :: y(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -750,7 +750,7 @@ subroutine psb_d_cxx_cssv(alpha,a,x,beta,y,info,trans)
logical :: tra,ctra logical :: tra,ctra
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_cssv' character(len=20) :: name='d_xyz_cssv'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
info = psb_success_ info = psb_success_
@ -805,7 +805,7 @@ subroutine psb_d_cxx_cssv(alpha,a,x,beta,y,info,trans)
if (beta == dzero) then if (beta == dzero) then
call inner_cxxsv(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),& call inner_xyzsv(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),&
& a%irp,a%ja,a%val,x,y) & a%irp,a%ja,a%val,x,y)
if (alpha == done) then if (alpha == done) then
! do nothing ! do nothing
@ -824,7 +824,7 @@ subroutine psb_d_cxx_cssv(alpha,a,x,beta,y,info,trans)
return return
end if end if
call inner_cxxsv(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),& call inner_xyzsv(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),&
& a%irp,a%ja,a%val,x,tmp) & a%irp,a%ja,a%val,x,tmp)
call psb_geaxpby(m,alpha,tmp,beta,y,info) call psb_geaxpby(m,alpha,tmp,beta,y,info)
@ -839,7 +839,7 @@ subroutine psb_d_cxx_cssv(alpha,a,x,beta,y,info,trans)
contains contains
subroutine inner_cxxsv(tra,ctra,lower,unit,n,irp,ja,val,x,y) subroutine inner_xyzsv(tra,ctra,lower,unit,n,irp,ja,val,x,y)
implicit none implicit none
logical, intent(in) :: tra,ctra,lower,unit logical, intent(in) :: tra,ctra,lower,unit
integer(psb_ipk_), intent(in) :: irp(*), ja(*),n integer(psb_ipk_), intent(in) :: irp(*), ja(*),n
@ -988,18 +988,18 @@ contains
end if end if
end if end if
end subroutine inner_cxxsv end subroutine inner_xyzsv
end subroutine psb_d_cxx_cssv end subroutine psb_d_xyz_cssv
subroutine psb_d_cxx_cssm(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_cssm(alpha,a,x,beta,y,info,trans)
use psb_error_mod use psb_error_mod
use psb_string_mod use psb_string_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_cssm use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_cssm
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:,:) real(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
real(psb_dpk_), intent(inout) :: y(:,:) real(psb_dpk_), intent(inout) :: y(:,:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -1012,7 +1012,7 @@ subroutine psb_d_cxx_cssm(alpha,a,x,beta,y,info,trans)
logical :: tra, ctra logical :: tra, ctra
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_cssm' character(len=20) :: name='d_xyz_cssm'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
info = psb_success_ info = psb_success_
@ -1057,7 +1057,7 @@ subroutine psb_d_cxx_cssm(alpha,a,x,beta,y,info,trans)
end if end if
if (beta == dzero) then if (beta == dzero) then
call inner_cxxsm(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),nc,& call inner_xyzsm(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),nc,&
& a%irp,a%ja,a%val,x,size(x,1,kind=psb_ipk_),y,size(y,1,kind=psb_ipk_),info) & a%irp,a%ja,a%val,x,size(x,1,kind=psb_ipk_),y,size(y,1,kind=psb_ipk_),info)
do i = 1, m do i = 1, m
y(i,1:nc) = alpha*y(i,1:nc) y(i,1:nc) = alpha*y(i,1:nc)
@ -1070,7 +1070,7 @@ subroutine psb_d_cxx_cssm(alpha,a,x,beta,y,info,trans)
goto 9999 goto 9999
end if end if
call inner_cxxsm(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),nc,& call inner_xyzsm(tra,ctra,a%is_lower(),a%is_unit(),a%get_nrows(),nc,&
& a%irp,a%ja,a%val,x,size(x,1,kind=psb_ipk_),tmp,size(tmp,1,kind=psb_ipk_),info) & a%irp,a%ja,a%val,x,size(x,1,kind=psb_ipk_),tmp,size(tmp,1,kind=psb_ipk_),info)
do i = 1, m do i = 1, m
y(i,1:nc) = alpha*tmp(i,1:nc) + beta*y(i,1:nc) y(i,1:nc) = alpha*tmp(i,1:nc) + beta*y(i,1:nc)
@ -1079,7 +1079,7 @@ subroutine psb_d_cxx_cssm(alpha,a,x,beta,y,info,trans)
if(info /= psb_success_) then if(info /= psb_success_) then
info=psb_err_from_subroutine_ info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='inner_cxxsm') call psb_errpush(info,name,a_err='inner_xyzsm')
goto 9999 goto 9999
end if end if
@ -1093,7 +1093,7 @@ subroutine psb_d_cxx_cssm(alpha,a,x,beta,y,info,trans)
contains contains
subroutine inner_cxxsm(tra,ctra,lower,unit,nr,nc,& subroutine inner_xyzsm(tra,ctra,lower,unit,nr,nc,&
& irp,ja,val,x,ldx,y,ldy,info) & irp,ja,val,x,ldx,y,ldy,info)
implicit none implicit none
logical, intent(in) :: tra,ctra,lower,unit logical, intent(in) :: tra,ctra,lower,unit
@ -1249,20 +1249,20 @@ contains
end if end if
end if end if
end subroutine inner_cxxsm end subroutine inner_xyzsm
end subroutine psb_d_cxx_cssm end subroutine psb_d_xyz_cssm
function psb_d_cxx_maxval(a) result(res) function psb_d_xyz_maxval(a) result(res)
use psb_error_mod use psb_error_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_maxval use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_maxval
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res real(psb_dpk_) :: res
integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc, info integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc, info
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_maxval' character(len=20) :: name='d_xyz_maxval'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -1272,13 +1272,13 @@ function psb_d_cxx_maxval(a) result(res)
nnz = min(nnz,size(a%val)) nnz = min(nnz,size(a%val))
res = maxval(abs(a%val(1:nnz))) res = maxval(abs(a%val(1:nnz)))
end if end if
end function psb_d_cxx_maxval end function psb_d_xyz_maxval
function psb_d_cxx_csnmi(a) result(res) function psb_d_xyz_csnmi(a) result(res)
use psb_error_mod use psb_error_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csnmi use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csnmi
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res real(psb_dpk_) :: res
integer(psb_ipk_) :: i,j,k,m,n, nr, ir, jc, nc integer(psb_ipk_) :: i,j,k,m,n, nr, ir, jc, nc
@ -1300,15 +1300,15 @@ function psb_d_cxx_csnmi(a) result(res)
res = max(res,acc) res = max(res,acc)
end do end do
end function psb_d_cxx_csnmi end function psb_d_xyz_csnmi
function psb_d_cxx_csnm1(a) result(res) function psb_d_xyz_csnm1(a) result(res)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csnm1 use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csnm1
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res real(psb_dpk_) :: res
integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc, info integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc, info
@ -1317,7 +1317,7 @@ function psb_d_cxx_csnm1(a) result(res)
logical :: tra logical :: tra
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_csnm1' character(len=20) :: name='d_xyz_csnm1'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
@ -1339,13 +1339,13 @@ function psb_d_cxx_csnm1(a) result(res)
return return
end function psb_d_cxx_csnm1 end function psb_d_xyz_csnm1
subroutine psb_d_cxx_rowsum(d,a) subroutine psb_d_xyz_rowsum(d,a)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_rowsum use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_rowsum
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc
@ -1387,13 +1387,13 @@ subroutine psb_d_cxx_rowsum(d,a)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_rowsum end subroutine psb_d_xyz_rowsum
subroutine psb_d_cxx_arwsum(d,a) subroutine psb_d_xyz_arwsum(d,a)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_arwsum use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_arwsum
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc
@ -1435,13 +1435,13 @@ subroutine psb_d_cxx_arwsum(d,a)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_arwsum end subroutine psb_d_xyz_arwsum
subroutine psb_d_cxx_colsum(d,a) subroutine psb_d_xyz_colsum(d,a)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_colsum use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_colsum
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc
@ -1486,13 +1486,13 @@ subroutine psb_d_cxx_colsum(d,a)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_colsum end subroutine psb_d_xyz_colsum
subroutine psb_d_cxx_aclsum(d,a) subroutine psb_d_xyz_aclsum(d,a)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_aclsum use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_aclsum
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc integer(psb_ipk_) :: i,j,k,m,n, nnz, ir, jc, nc
@ -1537,14 +1537,14 @@ subroutine psb_d_cxx_aclsum(d,a)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_aclsum end subroutine psb_d_xyz_aclsum
subroutine psb_d_cxx_get_diag(a,d,info) subroutine psb_d_xyz_get_diag(a,d,info)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_get_diag use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_get_diag
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -1588,16 +1588,16 @@ subroutine psb_d_cxx_get_diag(a,d,info)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_get_diag end subroutine psb_d_xyz_get_diag
subroutine psb_d_cxx_scal(d,a,info,side) subroutine psb_d_xyz_scal(d,a,info,side)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_scal use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_scal
use psb_string_mod use psb_string_mod
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
real(psb_dpk_), intent(in) :: d(:) real(psb_dpk_), intent(in) :: d(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character, intent(in), optional :: side character, intent(in), optional :: side
@ -1660,15 +1660,15 @@ subroutine psb_d_cxx_scal(d,a,info,side)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_scal end subroutine psb_d_xyz_scal
subroutine psb_d_cxx_scals(d,a,info) subroutine psb_d_xyz_scals(d,a,info)
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_scals use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_scals
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
real(psb_dpk_), intent(in) :: d real(psb_dpk_), intent(in) :: d
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -1694,7 +1694,7 @@ subroutine psb_d_cxx_scals(d,a,info)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_scals end subroutine psb_d_xyz_scals
@ -1712,16 +1712,16 @@ end subroutine psb_d_cxx_scals
! == =================================== ! == ===================================
subroutine psb_d_cxx_reallocate_nz(nz,a) subroutine psb_d_xyz_reallocate_nz(nz,a)
use psb_error_mod use psb_error_mod
use psb_realloc_mod use psb_realloc_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_reallocate_nz use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_reallocate_nz
implicit none implicit none
integer(psb_ipk_), intent(in) :: nz integer(psb_ipk_), intent(in) :: nz
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: err_act, info integer(psb_ipk_) :: err_act, info
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_reallocate_nz' character(len=20) :: name='d_xyz_reallocate_nz'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
call psb_erractionsave(err_act) call psb_erractionsave(err_act)
@ -1741,18 +1741,18 @@ subroutine psb_d_cxx_reallocate_nz(nz,a)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_reallocate_nz end subroutine psb_d_xyz_reallocate_nz
subroutine psb_d_cxx_mold(a,b,info) subroutine psb_d_xyz_mold(a,b,info)
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_mold use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_mold
use psb_error_mod use psb_error_mod
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_base_sparse_mat), intent(inout), allocatable :: b class(psb_d_base_sparse_mat), intent(inout), allocatable :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='cxx_mold' character(len=20) :: name='xyz_mold'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
call psb_get_erraction(err_act) call psb_get_erraction(err_act)
@ -1762,7 +1762,7 @@ subroutine psb_d_cxx_mold(a,b,info)
call b%free() call b%free()
deallocate(b,stat=info) deallocate(b,stat=info)
end if end if
if (info == 0) allocate(psb_d_cxx_sparse_mat :: b, stat=info) if (info == 0) allocate(psb_d_xyz_sparse_mat :: b, stat=info)
if (info /= 0) then if (info /= 0) then
info = psb_err_alloc_dealloc_ info = psb_err_alloc_dealloc_
@ -1774,15 +1774,15 @@ subroutine psb_d_cxx_mold(a,b,info)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_mold end subroutine psb_d_xyz_mold
subroutine psb_d_cxx_allocate_mnnz(m,n,a,nz) subroutine psb_d_xyz_allocate_mnnz(m,n,a,nz)
use psb_error_mod use psb_error_mod
use psb_realloc_mod use psb_realloc_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_allocate_mnnz use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_allocate_mnnz
implicit none implicit none
integer(psb_ipk_), intent(in) :: m,n integer(psb_ipk_), intent(in) :: m,n
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
integer(psb_ipk_), intent(in), optional :: nz integer(psb_ipk_), intent(in), optional :: nz
integer(psb_ipk_) :: err_act, info, nz_ integer(psb_ipk_) :: err_act, info, nz_
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
@ -1834,20 +1834,20 @@ subroutine psb_d_cxx_allocate_mnnz(m,n,a,nz)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_allocate_mnnz end subroutine psb_d_xyz_allocate_mnnz
subroutine psb_d_cxx_csgetptn(imin,imax,a,nz,ia,ja,info,& subroutine psb_d_xyz_csgetptn(imin,imax,a,nz,ia,ja,info,&
& jmin,jmax,iren,append,nzin,rscale,cscale) & jmin,jmax,iren,append,nzin,rscale,cscale)
! Output is always in COO format ! Output is always in COO format
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_error_mod use psb_error_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csgetptn use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csgetptn
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in) :: imin,imax integer(psb_ipk_), intent(in) :: imin,imax
integer(psb_ipk_), intent(out) :: nz integer(psb_ipk_), intent(out) :: nz
integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:) integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:)
@ -1908,7 +1908,7 @@ subroutine psb_d_cxx_csgetptn(imin,imax,a,nz,ia,ja,info,&
goto 9999 goto 9999
end if end if
call cxx_getptn(imin,imax,jmin_,jmax_,a,nz,ia,ja,nzin_,append_,info,iren) call xyz_getptn(imin,imax,jmin_,jmax_,a,nz,ia,ja,nzin_,append_,info,iren)
if (rscale_) then if (rscale_) then
do i=nzin_+1, nzin_+nz do i=nzin_+1, nzin_+nz
@ -1931,7 +1931,7 @@ subroutine psb_d_cxx_csgetptn(imin,imax,a,nz,ia,ja,info,&
contains contains
subroutine cxx_getptn(imin,imax,jmin,jmax,a,nz,ia,ja,nzin,append,info,& subroutine xyz_getptn(imin,imax,jmin,jmax,a,nz,ia,ja,nzin,append,info,&
& iren) & iren)
use psb_const_mod use psb_const_mod
@ -1940,7 +1940,7 @@ contains
use psb_sort_mod use psb_sort_mod
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_) :: imin,imax,jmin,jmax integer(psb_ipk_) :: imin,imax,jmin,jmax
integer(psb_ipk_), intent(out) :: nz integer(psb_ipk_), intent(out) :: nz
integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:) integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:)
@ -1950,7 +1950,7 @@ contains
integer(psb_ipk_), optional :: iren(:) integer(psb_ipk_), optional :: iren(:)
integer(psb_ipk_) :: nzin_, nza, idx,i,j,k, nzt, irw, lrw integer(psb_ipk_) :: nzin_, nza, idx,i,j,k, nzt, irw, lrw
integer(psb_ipk_) :: debug_level, debug_unit integer(psb_ipk_) :: debug_level, debug_unit
character(len=20) :: name='cxx_getptn' character(len=20) :: name='xyz_getptn'
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level() debug_level = psb_get_debug_level()
@ -2002,22 +2002,22 @@ contains
end do end do
end if end if
end subroutine cxx_getptn end subroutine xyz_getptn
end subroutine psb_d_cxx_csgetptn end subroutine psb_d_xyz_csgetptn
subroutine psb_d_cxx_csgetrow(imin,imax,a,nz,ia,ja,val,info,& subroutine psb_d_xyz_csgetrow(imin,imax,a,nz,ia,ja,val,info,&
& jmin,jmax,iren,append,nzin,rscale,cscale) & jmin,jmax,iren,append,nzin,rscale,cscale)
! Output is always in COO format ! Output is always in COO format
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_error_mod use psb_error_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csgetrow use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csgetrow
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in) :: imin,imax integer(psb_ipk_), intent(in) :: imin,imax
integer(psb_ipk_), intent(out) :: nz integer(psb_ipk_), intent(out) :: nz
integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:) integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:)
@ -2079,7 +2079,7 @@ subroutine psb_d_cxx_csgetrow(imin,imax,a,nz,ia,ja,val,info,&
goto 9999 goto 9999
end if end if
call cxx_getrow(imin,imax,jmin_,jmax_,a,nz,ia,ja,val,nzin_,append_,info,& call xyz_getrow(imin,imax,jmin_,jmax_,a,nz,ia,ja,val,nzin_,append_,info,&
& iren) & iren)
if (rscale_) then if (rscale_) then
@ -2103,7 +2103,7 @@ subroutine psb_d_cxx_csgetrow(imin,imax,a,nz,ia,ja,val,info,&
contains contains
subroutine cxx_getrow(imin,imax,jmin,jmax,a,nz,ia,ja,val,nzin,append,info,& subroutine xyz_getrow(imin,imax,jmin,jmax,a,nz,ia,ja,val,nzin,append,info,&
& iren) & iren)
use psb_const_mod use psb_const_mod
@ -2112,7 +2112,7 @@ contains
use psb_sort_mod use psb_sort_mod
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_) :: imin,imax,jmin,jmax integer(psb_ipk_) :: imin,imax,jmin,jmax
integer(psb_ipk_), intent(out) :: nz integer(psb_ipk_), intent(out) :: nz
integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:) integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:)
@ -2178,19 +2178,19 @@ contains
end do end do
end if end if
end subroutine cxx_getrow end subroutine xyz_getrow
end subroutine psb_d_cxx_csgetrow end subroutine psb_d_xyz_csgetrow
subroutine psb_d_cxx_csgetblk(imin,imax,a,b,info,& subroutine psb_d_xyz_csgetblk(imin,imax,a,b,info,&
& jmin,jmax,iren,append,rscale,cscale) & jmin,jmax,iren,append,rscale,cscale)
! Output is always in COO format ! Output is always in COO format
use psb_error_mod use psb_error_mod
use psb_const_mod use psb_const_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csgetblk use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csgetblk
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(in) :: imin,imax integer(psb_ipk_), intent(in) :: imin,imax
integer(psb_ipk_),intent(out) :: info integer(psb_ipk_),intent(out) :: info
@ -2234,17 +2234,17 @@ subroutine psb_d_cxx_csgetblk(imin,imax,a,b,info,&
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_csgetblk end subroutine psb_d_xyz_csgetblk
subroutine psb_d_cxx_csput_a(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl) subroutine psb_d_xyz_csput_a(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl)
use psb_error_mod use psb_error_mod
use psb_realloc_mod use psb_realloc_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_csput_a use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_csput_a
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
real(psb_dpk_), intent(in) :: val(:) real(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(in) :: nz, ia(:), ja(:), imin,imax,jmin,jmax integer(psb_ipk_), intent(in) :: nz, ia(:), ja(:), imin,imax,jmin,jmax
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2253,7 +2253,7 @@ subroutine psb_d_cxx_csput_a(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl)
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_csput' character(len=20) :: name='d_xyz_csput'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
integer(psb_ipk_) :: nza, i,j,k, nzl, isza integer(psb_ipk_) :: nza, i,j,k, nzl, isza
@ -2296,7 +2296,7 @@ subroutine psb_d_cxx_csput_a(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl)
info = psb_err_invalid_mat_state_ info = psb_err_invalid_mat_state_
else if (a%is_upd()) then else if (a%is_upd()) then
call psb_d_cxx_srch_upd(nz,ia,ja,val,a,& call psb_d_xyz_srch_upd(nz,ia,ja,val,a,&
& imin,imax,jmin,jmax,info,gtl) & imin,imax,jmin,jmax,info,gtl)
if (info /= psb_success_) then if (info /= psb_success_) then
@ -2322,7 +2322,7 @@ subroutine psb_d_cxx_csput_a(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl)
contains contains
subroutine psb_d_cxx_srch_upd(nz,ia,ja,val,a,& subroutine psb_d_xyz_srch_upd(nz,ia,ja,val,a,&
& imin,imax,jmin,jmax,info,gtl) & imin,imax,jmin,jmax,info,gtl)
use psb_const_mod use psb_const_mod
@ -2331,7 +2331,7 @@ contains
use psb_sort_mod use psb_sort_mod
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
integer(psb_ipk_), intent(in) :: nz, imin,imax,jmin,jmax integer(psb_ipk_), intent(in) :: nz, imin,imax,jmin,jmax
integer(psb_ipk_), intent(in) :: ia(:),ja(:) integer(psb_ipk_), intent(in) :: ia(:),ja(:)
real(psb_dpk_), intent(in) :: val(:) real(psb_dpk_), intent(in) :: val(:)
@ -2340,7 +2340,7 @@ contains
integer(psb_ipk_) :: i,ir,ic, ilr, ilc, ip, & integer(psb_ipk_) :: i,ir,ic, ilr, ilc, ip, &
& i1,i2,nr,nc,nnz,dupl,ng & i1,i2,nr,nc,nnz,dupl,ng
integer(psb_ipk_) :: debug_level, debug_unit integer(psb_ipk_) :: debug_level, debug_unit
character(len=20) :: name='d_cxx_srch_upd' character(len=20) :: name='d_xyz_srch_upd'
info = psb_success_ info = psb_success_
debug_unit = psb_get_debug_unit() debug_unit = psb_get_debug_unit()
@ -2515,17 +2515,17 @@ contains
end if end if
end subroutine psb_d_cxx_srch_upd end subroutine psb_d_xyz_srch_upd
end subroutine psb_d_cxx_csput_a end subroutine psb_d_xyz_csput_a
subroutine psb_d_cxx_reinit(a,clear) subroutine psb_d_xyz_reinit(a,clear)
use psb_error_mod use psb_error_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_reinit use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_reinit
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
logical, intent(in), optional :: clear logical, intent(in), optional :: clear
integer(psb_ipk_) :: err_act, info integer(psb_ipk_) :: err_act, info
@ -2562,14 +2562,14 @@ subroutine psb_d_cxx_reinit(a,clear)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_reinit end subroutine psb_d_xyz_reinit
subroutine psb_d_cxx_trim(a) subroutine psb_d_xyz_trim(a)
use psb_realloc_mod use psb_realloc_mod
use psb_error_mod use psb_error_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_trim use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_trim
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
integer(psb_ipk_) :: err_act, info, nz, m integer(psb_ipk_) :: err_act, info, nz, m
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='trim' character(len=20) :: name='trim'
@ -2591,22 +2591,22 @@ subroutine psb_d_cxx_trim(a)
9999 call psb_error_handler(err_act) 9999 call psb_error_handler(err_act)
return return
end subroutine psb_d_cxx_trim end subroutine psb_d_xyz_trim
subroutine psb_d_cxx_print(iout,a,iv,head,ivr,ivc) subroutine psb_d_xyz_print(iout,a,iv,head,ivr,ivc)
use psb_string_mod use psb_string_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cxx_print use psb_d_xyz_mat_mod, psb_protect_name => psb_d_xyz_print
implicit none implicit none
integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(in) :: iout
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in), optional :: iv(:) integer(psb_ipk_), intent(in), optional :: iv(:)
character(len=*), optional :: head character(len=*), optional :: head
integer(psb_ipk_), intent(in), optional :: ivr(:), ivc(:) integer(psb_ipk_), intent(in), optional :: ivr(:), ivc(:)
integer(psb_ipk_) :: err_act integer(psb_ipk_) :: err_act
integer(psb_ipk_) :: ierr(5) integer(psb_ipk_) :: ierr(5)
character(len=20) :: name='d_cxx_print' character(len=20) :: name='d_xyz_print'
logical, parameter :: debug=.false. logical, parameter :: debug=.false.
character(len=*), parameter :: datatype='real' character(len=*), parameter :: datatype='real'
character(len=80) :: frmtv character(len=80) :: frmtv
@ -2665,17 +2665,17 @@ subroutine psb_d_cxx_print(iout,a,iv,head,ivr,ivc)
endif endif
endif endif
end subroutine psb_d_cxx_print end subroutine psb_d_xyz_print
subroutine psb_d_cp_cxx_from_coo(a,b,info) subroutine psb_d_cp_xyz_from_coo(a,b,info)
use psb_const_mod use psb_const_mod
use psb_realloc_mod use psb_realloc_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cp_cxx_from_coo use psb_d_xyz_mat_mod, psb_protect_name => psb_d_cp_xyz_from_coo
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_coo_sparse_mat), intent(in) :: b class(psb_d_coo_sparse_mat), intent(in) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2693,17 +2693,17 @@ subroutine psb_d_cp_cxx_from_coo(a,b,info)
call tmp%cp_from_coo(b,info) call tmp%cp_from_coo(b,info)
if (info == psb_success_) call a%mv_from_coo(tmp,info) if (info == psb_success_) call a%mv_from_coo(tmp,info)
end subroutine psb_d_cp_cxx_from_coo end subroutine psb_d_cp_xyz_from_coo
subroutine psb_d_cp_cxx_to_coo(a,b,info) subroutine psb_d_cp_xyz_to_coo(a,b,info)
use psb_const_mod use psb_const_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cp_cxx_to_coo use psb_d_xyz_mat_mod, psb_protect_name => psb_d_cp_xyz_to_coo
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2735,17 +2735,17 @@ subroutine psb_d_cp_cxx_to_coo(a,b,info)
call b%fix(info) call b%fix(info)
end subroutine psb_d_cp_cxx_to_coo end subroutine psb_d_cp_xyz_to_coo
subroutine psb_d_mv_cxx_to_coo(a,b,info) subroutine psb_d_mv_xyz_to_coo(a,b,info)
use psb_const_mod use psb_const_mod
use psb_realloc_mod use psb_realloc_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_mv_cxx_to_coo use psb_d_xyz_mat_mod, psb_protect_name => psb_d_mv_xyz_to_coo
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2778,19 +2778,19 @@ subroutine psb_d_mv_cxx_to_coo(a,b,info)
call b%fix(info) call b%fix(info)
end subroutine psb_d_mv_cxx_to_coo end subroutine psb_d_mv_xyz_to_coo
subroutine psb_d_mv_cxx_from_coo(a,b,info) subroutine psb_d_mv_xyz_from_coo(a,b,info)
use psb_const_mod use psb_const_mod
use psb_realloc_mod use psb_realloc_mod
use psb_error_mod use psb_error_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_mv_cxx_from_coo use psb_d_xyz_mat_mod, psb_protect_name => psb_d_mv_xyz_from_coo
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2873,16 +2873,16 @@ subroutine psb_d_mv_cxx_from_coo(a,b,info)
endif endif
end subroutine psb_d_mv_cxx_from_coo end subroutine psb_d_mv_xyz_from_coo
subroutine psb_d_mv_cxx_to_fmt(a,b,info) subroutine psb_d_mv_xyz_to_fmt(a,b,info)
use psb_const_mod use psb_const_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_mv_cxx_to_fmt use psb_d_xyz_mat_mod, psb_protect_name => psb_d_mv_xyz_to_fmt
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), intent(inout) :: b class(psb_d_base_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2900,7 +2900,7 @@ subroutine psb_d_mv_cxx_to_fmt(a,b,info)
type is (psb_d_coo_sparse_mat) type is (psb_d_coo_sparse_mat)
call a%mv_to_coo(b,info) call a%mv_to_coo(b,info)
! Need to fix trivial copies! ! Need to fix trivial copies!
type is (psb_d_cxx_sparse_mat) type is (psb_d_xyz_sparse_mat)
b%psb_d_base_sparse_mat = a%psb_d_base_sparse_mat b%psb_d_base_sparse_mat = a%psb_d_base_sparse_mat
call move_alloc(a%irp, b%irp) call move_alloc(a%irp, b%irp)
call move_alloc(a%ja, b%ja) call move_alloc(a%ja, b%ja)
@ -2912,17 +2912,17 @@ subroutine psb_d_mv_cxx_to_fmt(a,b,info)
if (info == psb_success_) call b%mv_from_coo(tmp,info) if (info == psb_success_) call b%mv_from_coo(tmp,info)
end select end select
end subroutine psb_d_mv_cxx_to_fmt end subroutine psb_d_mv_xyz_to_fmt
subroutine psb_d_cp_cxx_to_fmt(a,b,info) subroutine psb_d_cp_xyz_to_fmt(a,b,info)
use psb_const_mod use psb_const_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_realloc_mod use psb_realloc_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cp_cxx_to_fmt use psb_d_xyz_mat_mod, psb_protect_name => psb_d_cp_xyz_to_fmt
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_base_sparse_mat), intent(inout) :: b class(psb_d_base_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2941,7 +2941,7 @@ subroutine psb_d_cp_cxx_to_fmt(a,b,info)
type is (psb_d_coo_sparse_mat) type is (psb_d_coo_sparse_mat)
call a%cp_to_coo(b,info) call a%cp_to_coo(b,info)
type is (psb_d_cxx_sparse_mat) type is (psb_d_xyz_sparse_mat)
b%psb_d_base_sparse_mat = a%psb_d_base_sparse_mat b%psb_d_base_sparse_mat = a%psb_d_base_sparse_mat
if (info == 0) call psb_safe_cpy( a%irp, b%irp , info) if (info == 0) call psb_safe_cpy( a%irp, b%irp , info)
if (info == 0) call psb_safe_cpy( a%ja , b%ja , info) if (info == 0) call psb_safe_cpy( a%ja , b%ja , info)
@ -2952,16 +2952,16 @@ subroutine psb_d_cp_cxx_to_fmt(a,b,info)
if (info == psb_success_) call b%mv_from_coo(tmp,info) if (info == psb_success_) call b%mv_from_coo(tmp,info)
end select end select
end subroutine psb_d_cp_cxx_to_fmt end subroutine psb_d_cp_xyz_to_fmt
subroutine psb_d_mv_cxx_from_fmt(a,b,info) subroutine psb_d_mv_xyz_from_fmt(a,b,info)
use psb_const_mod use psb_const_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_mv_cxx_from_fmt use psb_d_xyz_mat_mod, psb_protect_name => psb_d_mv_xyz_from_fmt
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), intent(inout) :: b class(psb_d_base_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -2979,7 +2979,7 @@ subroutine psb_d_mv_cxx_from_fmt(a,b,info)
type is (psb_d_coo_sparse_mat) type is (psb_d_coo_sparse_mat)
call a%mv_from_coo(b,info) call a%mv_from_coo(b,info)
type is (psb_d_cxx_sparse_mat) type is (psb_d_xyz_sparse_mat)
a%psb_d_base_sparse_mat = b%psb_d_base_sparse_mat a%psb_d_base_sparse_mat = b%psb_d_base_sparse_mat
call move_alloc(b%irp, a%irp) call move_alloc(b%irp, a%irp)
call move_alloc(b%ja, a%ja) call move_alloc(b%ja, a%ja)
@ -2991,18 +2991,18 @@ subroutine psb_d_mv_cxx_from_fmt(a,b,info)
if (info == psb_success_) call a%mv_from_coo(tmp,info) if (info == psb_success_) call a%mv_from_coo(tmp,info)
end select end select
end subroutine psb_d_mv_cxx_from_fmt end subroutine psb_d_mv_xyz_from_fmt
subroutine psb_d_cp_cxx_from_fmt(a,b,info) subroutine psb_d_cp_xyz_from_fmt(a,b,info)
use psb_const_mod use psb_const_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
use psb_realloc_mod use psb_realloc_mod
use psb_d_cxx_mat_mod, psb_protect_name => psb_d_cp_cxx_from_fmt use psb_d_xyz_mat_mod, psb_protect_name => psb_d_cp_xyz_from_fmt
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), intent(in) :: b class(psb_d_base_sparse_mat), intent(in) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
@ -3020,7 +3020,7 @@ subroutine psb_d_cp_cxx_from_fmt(a,b,info)
type is (psb_d_coo_sparse_mat) type is (psb_d_coo_sparse_mat)
call a%cp_from_coo(b,info) call a%cp_from_coo(b,info)
type is (psb_d_cxx_sparse_mat) type is (psb_d_xyz_sparse_mat)
a%psb_d_base_sparse_mat = b%psb_d_base_sparse_mat a%psb_d_base_sparse_mat = b%psb_d_base_sparse_mat
if (info == 0) call psb_safe_cpy( b%irp, a%irp , info) if (info == 0) call psb_safe_cpy( b%irp, a%irp , info)
if (info == 0) call psb_safe_cpy( b%ja , a%ja , info) if (info == 0) call psb_safe_cpy( b%ja , a%ja , info)
@ -3030,4 +3030,4 @@ subroutine psb_d_cp_cxx_from_fmt(a,b,info)
call b%cp_to_coo(tmp,info) call b%cp_to_coo(tmp,info)
if (info == psb_success_) call a%mv_from_coo(tmp,info) if (info == psb_success_) call a%mv_from_coo(tmp,info)
end select end select
end subroutine psb_d_cp_cxx_from_fmt end subroutine psb_d_cp_xyz_from_fmt

@ -30,26 +30,26 @@
!!$ !!$
!!$ !!$
! !
! package: psb_d_cxx_mat_mod ! package: psb_d_xyz_mat_mod
! !
! This module contains the definition of the psb_d_cxx_sparse_mat type ! This module contains the definition of the psb_d_xyz_sparse_mat type
! which is just an example of how to build a new storage format. ! which is just an example of how to build a new storage format.
! Indeed this is simply CSR under a new name. ! Indeed this is simply CSR under a new name.
! !
! Please refere to psb_d_base_mat_mod for a detailed description ! Please refere to psb_d_base_mat_mod for a detailed description
! of the various methods, and to psb_d_cxx_impl for implementation details. ! of the various methods, and to psb_d_xyz_impl for implementation details.
! !
module psb_d_cxx_mat_mod module psb_d_xyz_mat_mod
use psb_d_base_mat_mod use psb_d_base_mat_mod
!> \namespace psb_base_mod \class psb_d_cxx_sparse_mat !> \namespace psb_base_mod \class psb_d_xyz_sparse_mat
!! \extends psb_d_base_mat_mod::psb_d_base_sparse_mat !! \extends psb_d_base_mat_mod::psb_d_base_sparse_mat
!! !!
!! psb_d_cxx_sparse_mat type and the related methods. !! psb_d_xyz_sparse_mat type and the related methods.
!! This is a very common storage type, and is the default for assembled !! This is a very common storage type, and is the default for assembled
!! matrices in our library !! matrices in our library
type, extends(psb_d_base_sparse_mat) :: psb_d_cxx_sparse_mat type, extends(psb_d_base_sparse_mat) :: psb_d_xyz_sparse_mat
!> Pointers to beginning of rows in JA and VAL. !> Pointers to beginning of rows in JA and VAL.
integer(psb_ipk_), allocatable :: irp(:) integer(psb_ipk_), allocatable :: irp(:)
@ -59,245 +59,245 @@ module psb_d_cxx_mat_mod
real(psb_dpk_), allocatable :: val(:) real(psb_dpk_), allocatable :: val(:)
contains contains
procedure, pass(a) :: get_size => d_cxx_get_size procedure, pass(a) :: get_size => d_xyz_get_size
procedure, pass(a) :: get_nzeros => d_cxx_get_nzeros procedure, pass(a) :: get_nzeros => d_xyz_get_nzeros
procedure, nopass :: get_fmt => d_cxx_get_fmt procedure, nopass :: get_fmt => d_xyz_get_fmt
procedure, pass(a) :: sizeof => d_cxx_sizeof procedure, pass(a) :: sizeof => d_xyz_sizeof
procedure, pass(a) :: csmm => psb_d_cxx_csmm procedure, pass(a) :: csmm => psb_d_xyz_csmm
procedure, pass(a) :: csmv => psb_d_cxx_csmv procedure, pass(a) :: csmv => psb_d_xyz_csmv
procedure, pass(a) :: inner_cssm => psb_d_cxx_cssm procedure, pass(a) :: inner_cssm => psb_d_xyz_cssm
procedure, pass(a) :: inner_cssv => psb_d_cxx_cssv procedure, pass(a) :: inner_cssv => psb_d_xyz_cssv
procedure, pass(a) :: scals => psb_d_cxx_scals procedure, pass(a) :: scals => psb_d_xyz_scals
procedure, pass(a) :: scalv => psb_d_cxx_scal procedure, pass(a) :: scalv => psb_d_xyz_scal
procedure, pass(a) :: maxval => psb_d_cxx_maxval procedure, pass(a) :: maxval => psb_d_xyz_maxval
procedure, pass(a) :: spnmi => psb_d_cxx_csnmi procedure, pass(a) :: spnmi => psb_d_xyz_csnmi
procedure, pass(a) :: spnm1 => psb_d_cxx_csnm1 procedure, pass(a) :: spnm1 => psb_d_xyz_csnm1
procedure, pass(a) :: rowsum => psb_d_cxx_rowsum procedure, pass(a) :: rowsum => psb_d_xyz_rowsum
procedure, pass(a) :: arwsum => psb_d_cxx_arwsum procedure, pass(a) :: arwsum => psb_d_xyz_arwsum
procedure, pass(a) :: colsum => psb_d_cxx_colsum procedure, pass(a) :: colsum => psb_d_xyz_colsum
procedure, pass(a) :: aclsum => psb_d_cxx_aclsum procedure, pass(a) :: aclsum => psb_d_xyz_aclsum
procedure, pass(a) :: reallocate_nz => psb_d_cxx_reallocate_nz procedure, pass(a) :: reallocate_nz => psb_d_xyz_reallocate_nz
procedure, pass(a) :: allocate_mnnz => psb_d_cxx_allocate_mnnz procedure, pass(a) :: allocate_mnnz => psb_d_xyz_allocate_mnnz
procedure, pass(a) :: cp_to_coo => psb_d_cp_cxx_to_coo procedure, pass(a) :: cp_to_coo => psb_d_cp_xyz_to_coo
procedure, pass(a) :: cp_from_coo => psb_d_cp_cxx_from_coo procedure, pass(a) :: cp_from_coo => psb_d_cp_xyz_from_coo
procedure, pass(a) :: cp_to_fmt => psb_d_cp_cxx_to_fmt procedure, pass(a) :: cp_to_fmt => psb_d_cp_xyz_to_fmt
procedure, pass(a) :: cp_from_fmt => psb_d_cp_cxx_from_fmt procedure, pass(a) :: cp_from_fmt => psb_d_cp_xyz_from_fmt
procedure, pass(a) :: mv_to_coo => psb_d_mv_cxx_to_coo procedure, pass(a) :: mv_to_coo => psb_d_mv_xyz_to_coo
procedure, pass(a) :: mv_from_coo => psb_d_mv_cxx_from_coo procedure, pass(a) :: mv_from_coo => psb_d_mv_xyz_from_coo
procedure, pass(a) :: mv_to_fmt => psb_d_mv_cxx_to_fmt procedure, pass(a) :: mv_to_fmt => psb_d_mv_xyz_to_fmt
procedure, pass(a) :: mv_from_fmt => psb_d_mv_cxx_from_fmt procedure, pass(a) :: mv_from_fmt => psb_d_mv_xyz_from_fmt
procedure, pass(a) :: csput_a => psb_d_cxx_csput_a procedure, pass(a) :: csput_a => psb_d_xyz_csput_a
procedure, pass(a) :: get_diag => psb_d_cxx_get_diag procedure, pass(a) :: get_diag => psb_d_xyz_get_diag
procedure, pass(a) :: csgetptn => psb_d_cxx_csgetptn procedure, pass(a) :: csgetptn => psb_d_xyz_csgetptn
procedure, pass(a) :: csgetrow => psb_d_cxx_csgetrow procedure, pass(a) :: csgetrow => psb_d_xyz_csgetrow
procedure, pass(a) :: get_nz_row => d_cxx_get_nz_row procedure, pass(a) :: get_nz_row => d_xyz_get_nz_row
procedure, pass(a) :: reinit => psb_d_cxx_reinit procedure, pass(a) :: reinit => psb_d_xyz_reinit
procedure, pass(a) :: trim => psb_d_cxx_trim procedure, pass(a) :: trim => psb_d_xyz_trim
procedure, pass(a) :: print => psb_d_cxx_print procedure, pass(a) :: print => psb_d_xyz_print
procedure, pass(a) :: free => d_cxx_free procedure, pass(a) :: free => d_xyz_free
procedure, pass(a) :: mold => psb_d_cxx_mold procedure, pass(a) :: mold => psb_d_xyz_mold
end type psb_d_cxx_sparse_mat end type psb_d_xyz_sparse_mat
private :: d_cxx_get_nzeros, d_cxx_free, d_cxx_get_fmt, & private :: d_xyz_get_nzeros, d_xyz_free, d_xyz_get_fmt, &
& d_cxx_get_size, d_cxx_sizeof, d_cxx_get_nz_row & d_xyz_get_size, d_xyz_sizeof, d_xyz_get_nz_row
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!| \see psb_base_mat_mod::psb_base_reallocate_nz !| \see psb_base_mat_mod::psb_base_reallocate_nz
interface interface
subroutine psb_d_cxx_reallocate_nz(nz,a) subroutine psb_d_xyz_reallocate_nz(nz,a)
import :: psb_ipk_, psb_d_cxx_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat
integer(psb_ipk_), intent(in) :: nz integer(psb_ipk_), intent(in) :: nz
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
end subroutine psb_d_cxx_reallocate_nz end subroutine psb_d_xyz_reallocate_nz
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!| \see psb_base_mat_mod::psb_base_reinit !| \see psb_base_mat_mod::psb_base_reinit
interface interface
subroutine psb_d_cxx_reinit(a,clear) subroutine psb_d_xyz_reinit(a,clear)
import :: psb_ipk_, psb_d_cxx_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
logical, intent(in), optional :: clear logical, intent(in), optional :: clear
end subroutine psb_d_cxx_reinit end subroutine psb_d_xyz_reinit
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!| \see psb_base_mat_mod::psb_base_trim !| \see psb_base_mat_mod::psb_base_trim
interface interface
subroutine psb_d_cxx_trim(a) subroutine psb_d_xyz_trim(a)
import :: psb_ipk_, psb_d_cxx_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
end subroutine psb_d_cxx_trim end subroutine psb_d_xyz_trim
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!| \see psb_base_mat_mod::psb_base_mold !| \see psb_base_mat_mod::psb_base_mold
interface interface
subroutine psb_d_cxx_mold(a,b,info) subroutine psb_d_xyz_mold(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_base_sparse_mat, psb_long_int_k_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_base_sparse_mat, psb_long_int_k_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_base_sparse_mat), intent(inout), allocatable :: b class(psb_d_base_sparse_mat), intent(inout), allocatable :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_cxx_mold end subroutine psb_d_xyz_mold
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!| \see psb_base_mat_mod::psb_base_allocate_mnnz !| \see psb_base_mat_mod::psb_base_allocate_mnnz
interface interface
subroutine psb_d_cxx_allocate_mnnz(m,n,a,nz) subroutine psb_d_xyz_allocate_mnnz(m,n,a,nz)
import :: psb_ipk_, psb_d_cxx_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat
integer(psb_ipk_), intent(in) :: m,n integer(psb_ipk_), intent(in) :: m,n
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
integer(psb_ipk_), intent(in), optional :: nz integer(psb_ipk_), intent(in), optional :: nz
end subroutine psb_d_cxx_allocate_mnnz end subroutine psb_d_xyz_allocate_mnnz
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_print !! \see psb_d_base_mat_mod::psb_d_base_print
interface interface
subroutine psb_d_cxx_print(iout,a,iv,head,ivr,ivc) subroutine psb_d_xyz_print(iout,a,iv,head,ivr,ivc)
import :: psb_ipk_, psb_d_cxx_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat
integer(psb_ipk_), intent(in) :: iout integer(psb_ipk_), intent(in) :: iout
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in), optional :: iv(:) integer(psb_ipk_), intent(in), optional :: iv(:)
character(len=*), optional :: head character(len=*), optional :: head
integer(psb_ipk_), intent(in), optional :: ivr(:), ivc(:) integer(psb_ipk_), intent(in), optional :: ivr(:), ivc(:)
end subroutine psb_d_cxx_print end subroutine psb_d_xyz_print
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_cp_to_coo !! \see psb_d_base_mat_mod::psb_d_base_cp_to_coo
interface interface
subroutine psb_d_cp_cxx_to_coo(a,b,info) subroutine psb_d_cp_xyz_to_coo(a,b,info)
import :: psb_ipk_, psb_d_coo_sparse_mat, psb_d_cxx_sparse_mat import :: psb_ipk_, psb_d_coo_sparse_mat, psb_d_xyz_sparse_mat
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_cp_cxx_to_coo end subroutine psb_d_cp_xyz_to_coo
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_cp_from_coo !! \see psb_d_base_mat_mod::psb_d_base_cp_from_coo
interface interface
subroutine psb_d_cp_cxx_from_coo(a,b,info) subroutine psb_d_cp_xyz_from_coo(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_coo_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_coo_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_coo_sparse_mat), intent(in) :: b class(psb_d_coo_sparse_mat), intent(in) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_cp_cxx_from_coo end subroutine psb_d_cp_xyz_from_coo
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_cp_to_fmt !! \see psb_d_base_mat_mod::psb_d_base_cp_to_fmt
interface interface
subroutine psb_d_cp_cxx_to_fmt(a,b,info) subroutine psb_d_cp_xyz_to_fmt(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_base_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_base_sparse_mat
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_base_sparse_mat), intent(inout) :: b class(psb_d_base_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_cp_cxx_to_fmt end subroutine psb_d_cp_xyz_to_fmt
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_cp_from_fmt !! \see psb_d_base_mat_mod::psb_d_base_cp_from_fmt
interface interface
subroutine psb_d_cp_cxx_from_fmt(a,b,info) subroutine psb_d_cp_xyz_from_fmt(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_base_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_base_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), intent(in) :: b class(psb_d_base_sparse_mat), intent(in) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_cp_cxx_from_fmt end subroutine psb_d_cp_xyz_from_fmt
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_mv_to_coo !! \see psb_d_base_mat_mod::psb_d_base_mv_to_coo
interface interface
subroutine psb_d_mv_cxx_to_coo(a,b,info) subroutine psb_d_mv_xyz_to_coo(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_coo_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_coo_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_mv_cxx_to_coo end subroutine psb_d_mv_xyz_to_coo
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_mv_from_coo !! \see psb_d_base_mat_mod::psb_d_base_mv_from_coo
interface interface
subroutine psb_d_mv_cxx_from_coo(a,b,info) subroutine psb_d_mv_xyz_from_coo(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_coo_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_coo_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_mv_cxx_from_coo end subroutine psb_d_mv_xyz_from_coo
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_mv_to_fmt !! \see psb_d_base_mat_mod::psb_d_base_mv_to_fmt
interface interface
subroutine psb_d_mv_cxx_to_fmt(a,b,info) subroutine psb_d_mv_xyz_to_fmt(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_base_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_base_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), intent(inout) :: b class(psb_d_base_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_mv_cxx_to_fmt end subroutine psb_d_mv_xyz_to_fmt
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_mv_from_fmt !! \see psb_d_base_mat_mod::psb_d_base_mv_from_fmt
interface interface
subroutine psb_d_mv_cxx_from_fmt(a,b,info) subroutine psb_d_mv_xyz_from_fmt(a,b,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_d_base_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_d_base_sparse_mat
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
class(psb_d_base_sparse_mat), intent(inout) :: b class(psb_d_base_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_mv_cxx_from_fmt end subroutine psb_d_mv_xyz_from_fmt
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_cp_from !! \see psb_d_base_mat_mod::psb_d_base_cp_from
interface interface
subroutine psb_d_cxx_cp_from(a,b) subroutine psb_d_xyz_cp_from(a,b)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
type(psb_d_cxx_sparse_mat), intent(in) :: b type(psb_d_xyz_sparse_mat), intent(in) :: b
end subroutine psb_d_cxx_cp_from end subroutine psb_d_xyz_cp_from
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_mv_from !! \see psb_d_base_mat_mod::psb_d_base_mv_from
interface interface
subroutine psb_d_cxx_mv_from(a,b) subroutine psb_d_xyz_mv_from(a,b)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
type(psb_d_cxx_sparse_mat), intent(inout) :: b type(psb_d_xyz_sparse_mat), intent(inout) :: b
end subroutine psb_d_cxx_mv_from end subroutine psb_d_xyz_mv_from
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_csput !! \see psb_d_base_mat_mod::psb_d_base_csput
interface interface
subroutine psb_d_cxx_csput_a(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl) subroutine psb_d_xyz_csput_a(nz,ia,ja,val,a,imin,imax,jmin,jmax,info,gtl)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
real(psb_dpk_), intent(in) :: val(:) real(psb_dpk_), intent(in) :: val(:)
integer(psb_ipk_), intent(in) :: nz,ia(:), ja(:),& integer(psb_ipk_), intent(in) :: nz,ia(:), ja(:),&
& imin,imax,jmin,jmax & imin,imax,jmin,jmax
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_), intent(in), optional :: gtl(:) integer(psb_ipk_), intent(in), optional :: gtl(:)
end subroutine psb_d_cxx_csput_a end subroutine psb_d_xyz_csput_a
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_base_mat_mod::psb_base_csgetptn !! \see psb_base_mat_mod::psb_base_csgetptn
interface interface
subroutine psb_d_cxx_csgetptn(imin,imax,a,nz,ia,ja,info,& subroutine psb_d_xyz_csgetptn(imin,imax,a,nz,ia,ja,info,&
& jmin,jmax,iren,append,nzin,rscale,cscale) & jmin,jmax,iren,append,nzin,rscale,cscale)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in) :: imin,imax integer(psb_ipk_), intent(in) :: imin,imax
integer(psb_ipk_), intent(out) :: nz integer(psb_ipk_), intent(out) :: nz
integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:) integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:)
@ -306,16 +306,16 @@ module psb_d_cxx_mat_mod
integer(psb_ipk_), intent(in), optional :: iren(:) integer(psb_ipk_), intent(in), optional :: iren(:)
integer(psb_ipk_), intent(in), optional :: jmin,jmax, nzin integer(psb_ipk_), intent(in), optional :: jmin,jmax, nzin
logical, intent(in), optional :: rscale,cscale logical, intent(in), optional :: rscale,cscale
end subroutine psb_d_cxx_csgetptn end subroutine psb_d_xyz_csgetptn
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_csgetrow !! \see psb_d_base_mat_mod::psb_d_base_csgetrow
interface interface
subroutine psb_d_cxx_csgetrow(imin,imax,a,nz,ia,ja,val,info,& subroutine psb_d_xyz_csgetrow(imin,imax,a,nz,ia,ja,val,info,&
& jmin,jmax,iren,append,nzin,rscale,cscale) & jmin,jmax,iren,append,nzin,rscale,cscale)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in) :: imin,imax integer(psb_ipk_), intent(in) :: imin,imax
integer(psb_ipk_), intent(out) :: nz integer(psb_ipk_), intent(out) :: nz
integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:) integer(psb_ipk_), allocatable, intent(inout) :: ia(:), ja(:)
@ -325,16 +325,16 @@ module psb_d_cxx_mat_mod
integer(psb_ipk_), intent(in), optional :: iren(:) integer(psb_ipk_), intent(in), optional :: iren(:)
integer(psb_ipk_), intent(in), optional :: jmin,jmax, nzin integer(psb_ipk_), intent(in), optional :: jmin,jmax, nzin
logical, intent(in), optional :: rscale,cscale logical, intent(in), optional :: rscale,cscale
end subroutine psb_d_cxx_csgetrow end subroutine psb_d_xyz_csgetrow
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_csgetblk !! \see psb_d_base_mat_mod::psb_d_base_csgetblk
interface interface
subroutine psb_d_cxx_csgetblk(imin,imax,a,b,info,& subroutine psb_d_xyz_csgetblk(imin,imax,a,b,info,&
& jmin,jmax,iren,append,rscale,cscale) & jmin,jmax,iren,append,rscale,cscale)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_, psb_d_coo_sparse_mat import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_, psb_d_coo_sparse_mat
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
class(psb_d_coo_sparse_mat), intent(inout) :: b class(psb_d_coo_sparse_mat), intent(inout) :: b
integer(psb_ipk_), intent(in) :: imin,imax integer(psb_ipk_), intent(in) :: imin,imax
integer(psb_ipk_),intent(out) :: info integer(psb_ipk_),intent(out) :: info
@ -342,163 +342,163 @@ module psb_d_cxx_mat_mod
integer(psb_ipk_), intent(in), optional :: iren(:) integer(psb_ipk_), intent(in), optional :: iren(:)
integer(psb_ipk_), intent(in), optional :: jmin,jmax integer(psb_ipk_), intent(in), optional :: jmin,jmax
logical, intent(in), optional :: rscale,cscale logical, intent(in), optional :: rscale,cscale
end subroutine psb_d_cxx_csgetblk end subroutine psb_d_xyz_csgetblk
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_cssv !! \see psb_d_base_mat_mod::psb_d_base_cssv
interface interface
subroutine psb_d_cxx_cssv(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_cssv(alpha,a,x,beta,y,info,trans)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:) real(psb_dpk_), intent(in) :: alpha, beta, x(:)
real(psb_dpk_), intent(inout) :: y(:) real(psb_dpk_), intent(inout) :: y(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character, optional, intent(in) :: trans character, optional, intent(in) :: trans
end subroutine psb_d_cxx_cssv end subroutine psb_d_xyz_cssv
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_cssm !! \see psb_d_base_mat_mod::psb_d_base_cssm
interface interface
subroutine psb_d_cxx_cssm(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_cssm(alpha,a,x,beta,y,info,trans)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:,:) real(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
real(psb_dpk_), intent(inout) :: y(:,:) real(psb_dpk_), intent(inout) :: y(:,:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character, optional, intent(in) :: trans character, optional, intent(in) :: trans
end subroutine psb_d_cxx_cssm end subroutine psb_d_xyz_cssm
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_csmv !! \see psb_d_base_mat_mod::psb_d_base_csmv
interface interface
subroutine psb_d_cxx_csmv(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_csmv(alpha,a,x,beta,y,info,trans)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:) real(psb_dpk_), intent(in) :: alpha, beta, x(:)
real(psb_dpk_), intent(inout) :: y(:) real(psb_dpk_), intent(inout) :: y(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character, optional, intent(in) :: trans character, optional, intent(in) :: trans
end subroutine psb_d_cxx_csmv end subroutine psb_d_xyz_csmv
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_csmm !! \see psb_d_base_mat_mod::psb_d_base_csmm
interface interface
subroutine psb_d_cxx_csmm(alpha,a,x,beta,y,info,trans) subroutine psb_d_xyz_csmm(alpha,a,x,beta,y,info,trans)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(in) :: alpha, beta, x(:,:) real(psb_dpk_), intent(in) :: alpha, beta, x(:,:)
real(psb_dpk_), intent(inout) :: y(:,:) real(psb_dpk_), intent(inout) :: y(:,:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character, optional, intent(in) :: trans character, optional, intent(in) :: trans
end subroutine psb_d_cxx_csmm end subroutine psb_d_xyz_csmm
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_maxval !! \see psb_d_base_mat_mod::psb_d_base_maxval
interface interface
function psb_d_cxx_maxval(a) result(res) function psb_d_xyz_maxval(a) result(res)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res real(psb_dpk_) :: res
end function psb_d_cxx_maxval end function psb_d_xyz_maxval
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_csnmi !! \see psb_d_base_mat_mod::psb_d_base_csnmi
interface interface
function psb_d_cxx_csnmi(a) result(res) function psb_d_xyz_csnmi(a) result(res)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res real(psb_dpk_) :: res
end function psb_d_cxx_csnmi end function psb_d_xyz_csnmi
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_csnm1 !! \see psb_d_base_mat_mod::psb_d_base_csnm1
interface interface
function psb_d_cxx_csnm1(a) result(res) function psb_d_xyz_csnm1(a) result(res)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_) :: res real(psb_dpk_) :: res
end function psb_d_cxx_csnm1 end function psb_d_xyz_csnm1
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_rowsum !! \see psb_d_base_mat_mod::psb_d_base_rowsum
interface interface
subroutine psb_d_cxx_rowsum(d,a) subroutine psb_d_xyz_rowsum(d,a)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
end subroutine psb_d_cxx_rowsum end subroutine psb_d_xyz_rowsum
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_arwsum !! \see psb_d_base_mat_mod::psb_d_base_arwsum
interface interface
subroutine psb_d_cxx_arwsum(d,a) subroutine psb_d_xyz_arwsum(d,a)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
end subroutine psb_d_cxx_arwsum end subroutine psb_d_xyz_arwsum
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_colsum !! \see psb_d_base_mat_mod::psb_d_base_colsum
interface interface
subroutine psb_d_cxx_colsum(d,a) subroutine psb_d_xyz_colsum(d,a)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
end subroutine psb_d_cxx_colsum end subroutine psb_d_xyz_colsum
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_aclsum !! \see psb_d_base_mat_mod::psb_d_base_aclsum
interface interface
subroutine psb_d_cxx_aclsum(d,a) subroutine psb_d_xyz_aclsum(d,a)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
end subroutine psb_d_cxx_aclsum end subroutine psb_d_xyz_aclsum
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_get_diag !! \see psb_d_base_mat_mod::psb_d_base_get_diag
interface interface
subroutine psb_d_cxx_get_diag(a,d,info) subroutine psb_d_xyz_get_diag(a,d,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
real(psb_dpk_), intent(out) :: d(:) real(psb_dpk_), intent(out) :: d(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_cxx_get_diag end subroutine psb_d_xyz_get_diag
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_scal !! \see psb_d_base_mat_mod::psb_d_base_scal
interface interface
subroutine psb_d_cxx_scal(d,a,info,side) subroutine psb_d_xyz_scal(d,a,info,side)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
real(psb_dpk_), intent(in) :: d(:) real(psb_dpk_), intent(in) :: d(:)
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
character, intent(in), optional :: side character, intent(in), optional :: side
end subroutine psb_d_cxx_scal end subroutine psb_d_xyz_scal
end interface end interface
!> \memberof psb_d_cxx_sparse_mat !> \memberof psb_d_xyz_sparse_mat
!! \see psb_d_base_mat_mod::psb_d_base_scals !! \see psb_d_base_mat_mod::psb_d_base_scals
interface interface
subroutine psb_d_cxx_scals(d,a,info) subroutine psb_d_xyz_scals(d,a,info)
import :: psb_ipk_, psb_d_cxx_sparse_mat, psb_dpk_ import :: psb_ipk_, psb_d_xyz_sparse_mat, psb_dpk_
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
real(psb_dpk_), intent(in) :: d real(psb_dpk_), intent(in) :: d
integer(psb_ipk_), intent(out) :: info integer(psb_ipk_), intent(out) :: info
end subroutine psb_d_cxx_scals end subroutine psb_d_xyz_scals
end interface end interface
@ -518,33 +518,33 @@ contains
! == =================================== ! == ===================================
function d_cxx_sizeof(a) result(res) function d_xyz_sizeof(a) result(res)
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_long_int_k_) :: res integer(psb_long_int_k_) :: res
res = 8 res = 8
res = res + psb_sizeof_dp * size(a%val) res = res + psb_sizeof_dp * size(a%val)
res = res + psb_sizeof_int * size(a%irp) res = res + psb_sizeof_int * size(a%irp)
res = res + psb_sizeof_int * size(a%ja) res = res + psb_sizeof_int * size(a%ja)
end function d_cxx_sizeof end function d_xyz_sizeof
function d_cxx_get_fmt() result(res) function d_xyz_get_fmt() result(res)
implicit none implicit none
character(len=5) :: res character(len=5) :: res
res = 'CXX' res = 'XYZ'
end function d_cxx_get_fmt end function d_xyz_get_fmt
function d_cxx_get_nzeros(a) result(res) function d_xyz_get_nzeros(a) result(res)
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_) :: res integer(psb_ipk_) :: res
res = a%irp(a%get_nrows()+1)-1 res = a%irp(a%get_nrows()+1)-1
end function d_cxx_get_nzeros end function d_xyz_get_nzeros
function d_cxx_get_size(a) result(res) function d_xyz_get_size(a) result(res)
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_) :: res integer(psb_ipk_) :: res
res = -1 res = -1
@ -560,15 +560,15 @@ contains
end if end if
end if end if
end function d_cxx_get_size end function d_xyz_get_size
function d_cxx_get_nz_row(idx,a) result(res) function d_xyz_get_nz_row(idx,a) result(res)
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(in) :: a class(psb_d_xyz_sparse_mat), intent(in) :: a
integer(psb_ipk_), intent(in) :: idx integer(psb_ipk_), intent(in) :: idx
integer(psb_ipk_) :: res integer(psb_ipk_) :: res
@ -578,7 +578,7 @@ contains
res = a%irp(idx+1)-a%irp(idx) res = a%irp(idx+1)-a%irp(idx)
end if end if
end function d_cxx_get_nz_row end function d_xyz_get_nz_row
@ -594,10 +594,10 @@ contains
! !
! == =================================== ! == ===================================
subroutine d_cxx_free(a) subroutine d_xyz_free(a)
implicit none implicit none
class(psb_d_cxx_sparse_mat), intent(inout) :: a class(psb_d_xyz_sparse_mat), intent(inout) :: a
if (allocated(a%irp)) deallocate(a%irp) if (allocated(a%irp)) deallocate(a%irp)
if (allocated(a%ja)) deallocate(a%ja) if (allocated(a%ja)) deallocate(a%ja)
@ -608,7 +608,7 @@ contains
return return
end subroutine d_cxx_free end subroutine d_xyz_free
end module psb_d_cxx_mat_mod end module psb_d_xyz_mat_mod
Loading…
Cancel
Save