Change constant name to psb_c_Xpk_

merge-paraggr
Salvatore Filippone 5 years ago
parent 71059dc783
commit 3cc63f7e84

@ -9,14 +9,14 @@ contains
function psb_c_error() bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
res = 0
call psb_error()
end function psb_c_error
function psb_c_clean_errstack() bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
res = 0
call psb_clean_errstack()
end function psb_c_clean_errstack
@ -24,13 +24,13 @@ contains
function psb_c_cdall_vg(ng,vg,ictxt,cdh) bind(c,name='psb_c_cdall_vg') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_lpk), value :: ng
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk) :: vg(*)
integer(psb_c_ipk_) :: res
integer(psb_c_lpk_), value :: ng
integer(psb_c_ipk_), value :: ictxt
integer(psb_c_ipk_) :: vg(*)
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (ng <=0) then
@ -58,12 +58,12 @@ contains
function psb_c_cdall_vl(nl,vl,ictxt,cdh) bind(c,name='psb_c_cdall_vl') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nl, ictxt
integer(psb_c_lpk) :: vl(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nl, ictxt
integer(psb_c_lpk_) :: vl(*)
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
integer(psb_c_ipk) :: info, ixb
integer(psb_c_ipk_) :: info, ixb
res = -1
if (nl <=0) then
@ -96,11 +96,11 @@ contains
function psb_c_cdall_nl(nl,ictxt,cdh) bind(c,name='psb_c_cdall_nl') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nl, ictxt
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nl, ictxt
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (nl <=0) then
@ -127,12 +127,12 @@ contains
function psb_c_cdall_repl(n,ictxt,cdh) bind(c,name='psb_c_cdall_repl') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_lpk), value :: n
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_) :: res
integer(psb_c_lpk_), value :: n
integer(psb_c_ipk_), value :: ictxt
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (n <=0) then
@ -159,10 +159,10 @@ contains
function psb_c_cdasb(cdh) bind(c,name='psb_c_cdasb') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -178,10 +178,10 @@ contains
function psb_c_cdfree(cdh) bind(c,name='psb_c_cdfree') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -199,13 +199,13 @@ contains
function psb_c_cdins(nz,ia,ja,cdh) bind(c,name='psb_c_cdins') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
type(psb_c_object_type) :: cdh
integer(psb_c_lpk) :: ia(*),ja(*)
integer(psb_c_lpk_) :: ia(*),ja(*)
type(psb_desc_type), pointer :: descp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -222,7 +222,7 @@ contains
function psb_c_cd_get_local_rows(cdh) bind(c,name='psb_c_cd_get_local_rows') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
@ -243,7 +243,7 @@ contains
function psb_c_cd_get_local_cols(cdh) bind(c,name='psb_c_cd_get_local_cols') result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
@ -262,7 +262,7 @@ contains
function psb_c_cd_get_global_rows(cdh) bind(c,name='psb_c_cd_get_global_rows') result(res)
implicit none
integer(psb_c_lpk) :: res
integer(psb_c_lpk_) :: res
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp
@ -283,7 +283,7 @@ contains
function psb_c_cd_get_global_cols(cdh) bind(c,name='psb_c_cd_get_global_cols') result(res)
implicit none
integer(psb_c_lpk) :: res
integer(psb_c_lpk_) :: res
type(psb_c_object_type) :: cdh
type(psb_desc_type), pointer :: descp

@ -8,14 +8,14 @@ contains
function psb_c_c_ovrl(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -39,15 +39,15 @@ contains
function psb_c_c_ovrl_opt(xh,cdh,update,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: update, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: update, mode
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -72,14 +72,14 @@ contains
function psb_c_c_halo(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -103,8 +103,8 @@ contains
function psb_c_c_halo_opt(xh,cdh,tran,data,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: data, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: data, mode
character(c_char) :: tran
@ -114,7 +114,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
character :: ftran
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -141,8 +141,8 @@ contains
function psb_c_c_vscatter(ng,gx,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_lpk), value :: ng
integer(psb_c_ipk_) :: res
integer(psb_c_lpk_), value :: ng
complex(c_float_complex), target :: gx(*)
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
@ -150,7 +150,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: vp
complex(psb_spk_), pointer :: pgx(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -175,7 +175,7 @@ contains
function psb_c_cvgather(v,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
complex(c_float_complex), target :: v(*)
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
@ -183,7 +183,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: vp
complex(psb_spk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -208,13 +208,13 @@ contains
function psb_c_cspgather(gah,ah,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: ah, gah
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap, gap
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
if (c_associated(cdh%item)) then

@ -8,7 +8,7 @@ contains
function psb_c_cgeaxpby(alpha,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh,yh
type(psb_c_descriptor) :: cdh
@ -16,7 +16,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -51,7 +51,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -78,7 +78,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -104,7 +104,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -132,7 +132,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -158,7 +158,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -183,7 +183,7 @@ contains
function psb_c_cspmm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: ah
type(psb_c_cvector) :: xh,yh
@ -192,7 +192,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp,yp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -225,7 +225,7 @@ contains
function psb_c_cspmm_opt(alpha,ah,xh,beta,yh,cdh,trans,doswap) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: ah
type(psb_c_cvector) :: xh,yh
@ -239,7 +239,7 @@ contains
type(psb_cspmat_type), pointer :: ap
character :: ftrans
logical :: fdoswap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -274,7 +274,7 @@ contains
function psb_c_cspsm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: ah
type(psb_c_cvector) :: xh,yh
@ -283,7 +283,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp,yp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then

@ -11,11 +11,11 @@ contains
function psb_c_cvect_get_nrows(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh
type(psb_c_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -29,13 +29,13 @@ contains
function psb_c_cvect_f_get_cpy(v,xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
complex(c_float_complex) :: v(*)
type(psb_c_cvector) :: xh
type(psb_c_vect_type), pointer :: vp
complex(psb_spk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -52,11 +52,11 @@ contains
function psb_c_cvect_zero(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh
type(psb_c_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -73,11 +73,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: mh
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -96,11 +96,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: mh
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -119,12 +119,12 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
character(c_char) :: name(*)
type(psb_c_cspmat) :: mh
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(1024) :: fname
res = 0

@ -11,13 +11,13 @@ contains
function psb_c_cgeall(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -40,13 +40,13 @@ contains
function psb_c_cgeasb(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -70,13 +70,13 @@ contains
function psb_c_cgefree(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -102,16 +102,16 @@ contains
function psb_c_cgeins(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
complex(c_float_complex) :: val(*)
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -143,16 +143,16 @@ contains
function psb_c_cgeins_add(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
complex(c_float_complex) :: val(*)
type(psb_c_cvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_c_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -183,13 +183,13 @@ contains
function psb_c_cspall(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -213,13 +213,13 @@ contains
function psb_c_cspasb(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -242,13 +242,13 @@ contains
function psb_c_cspfree(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -277,10 +277,10 @@ contains
use psb_c_rsb_mat_mod
#endif
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: cdh, mh,upd,dupl
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: cdh, mh,upd,dupl
character(c_char) :: afmt(*)
integer(psb_c_ipk) :: info,n, fdupl
integer(psb_c_ipk_) :: info,n, fdupl
character(len=5) :: fafmt
#ifdef HAVE_LIBRSB
type(psb_c_rsb_sparse_mat) :: arsb
@ -313,16 +313,16 @@ contains
function psb_c_cspins(nz,irw,icl,val,mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*), icl(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*), icl(*)
complex(c_float_complex) :: val(*)
type(psb_c_cspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: ixb,info,n
integer(psb_c_ipk_) :: ixb,info,n
res = -1
if (c_associated(cdh%item)) then
@ -350,14 +350,14 @@ contains
function psb_c_csprn(mh,cdh,clear) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
logical(c_bool), value :: clear
type(psb_c_cspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
logical :: fclear
res = -1
@ -382,9 +382,9 @@ contains
!!$ function psb_c_cspprint(mh) bind(c) result(res)
!!$
!!$ implicit none
!!$ integer(psb_c_ipk) :: res
!!$ integer(psb_c_ipk), value :: mh
!!$ integer(psb_c_ipk) :: info
!!$ integer(psb_c_ipk_) :: res
!!$ integer(psb_c_ipk_), value :: mh
!!$ integer(psb_c_ipk_) :: info
!!$
!!$
!!$ res = -1

@ -9,14 +9,14 @@ contains
function psb_c_get_index_base() bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
res = psb_c_index_base
end function psb_c_get_index_base
subroutine psb_c_set_index_base(base) bind(c)
implicit none
integer(psb_c_ipk), value :: base
integer(psb_c_ipk_), value :: base
psb_c_index_base = base
end subroutine psb_c_set_index_base
@ -25,7 +25,7 @@ contains
use psb_base_mod, only : psb_get_errstatus
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
res = psb_get_errstatus()
end function psb_c_get_errstatus
@ -34,7 +34,7 @@ contains
use psb_base_mod, only : psb_init
implicit none
integer(psb_c_ipk) :: psb_c_init
integer(psb_c_ipk_) :: psb_c_init
integer :: ictxt
@ -44,7 +44,7 @@ contains
subroutine psb_c_exit_ctxt(ictxt) bind(c)
use psb_base_mod, only : psb_exit
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_), value :: ictxt
call psb_exit(ictxt,close=.false.)
return
@ -52,7 +52,7 @@ contains
subroutine psb_c_exit(ictxt) bind(c)
use psb_base_mod, only : psb_exit
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_), value :: ictxt
call psb_exit(ictxt)
return
@ -60,7 +60,7 @@ contains
subroutine psb_c_abort(ictxt) bind(c)
use psb_base_mod, only : psb_abort
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_), value :: ictxt
call psb_abort(ictxt)
return
@ -69,8 +69,8 @@ contains
subroutine psb_c_info(ictxt,iam,np) bind(c)
use psb_base_mod, only : psb_info
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk) :: iam,np
integer(psb_c_ipk_), value :: ictxt
integer(psb_c_ipk_) :: iam,np
call psb_info(ictxt,iam,np)
return
@ -78,7 +78,7 @@ contains
subroutine psb_c_barrier(ictxt) bind(c)
use psb_base_mod, only : psb_barrier
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_), value :: ictxt
call psb_barrier(ictxt)
end subroutine psb_c_barrier
@ -92,8 +92,8 @@ contains
subroutine psb_c_mbcast(ictxt,n,v,root) bind(c)
use psb_base_mod, only : psb_bcast
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_mpk) :: v(*)
integer(psb_c_ipk_), value :: ictxt,n, root
integer(psb_c_mpk_) :: v(*)
if (n < 0) then
write(0,*) 'Wrong size in BCAST'
@ -107,8 +107,8 @@ contains
subroutine psb_c_ibcast(ictxt,n,v,root) bind(c)
use psb_base_mod, only : psb_bcast
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_ipk) :: v(*)
integer(psb_c_ipk_), value :: ictxt,n, root
integer(psb_c_ipk_) :: v(*)
if (n < 0) then
write(0,*) 'Wrong size in BCAST'
@ -122,8 +122,8 @@ contains
subroutine psb_c_lbcast(ictxt,n,v,root) bind(c)
use psb_base_mod, only : psb_bcast
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_lpk) :: v(*)
integer(psb_c_ipk_), value :: ictxt,n, root
integer(psb_c_lpk_) :: v(*)
if (n < 0) then
write(0,*) 'Wrong size in BCAST'
@ -137,8 +137,8 @@ contains
subroutine psb_c_ebcast(ictxt,n,v,root) bind(c)
use psb_base_mod, only : psb_bcast
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_epk) :: v(*)
integer(psb_c_ipk_), value :: ictxt,n, root
integer(psb_c_epk_) :: v(*)
if (n < 0) then
write(0,*) 'Wrong size in BCAST'
@ -152,7 +152,7 @@ contains
subroutine psb_c_sbcast(ictxt,n,v,root) bind(c)
use psb_base_mod
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_ipk_), value :: ictxt,n, root
real(c_float) :: v(*)
if (n < 0) then
@ -167,7 +167,7 @@ contains
subroutine psb_c_dbcast(ictxt,n,v,root) bind(c)
use psb_base_mod, only : psb_bcast
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_ipk_), value :: ictxt,n, root
real(c_double) :: v(*)
if (n < 0) then
@ -183,7 +183,7 @@ contains
subroutine psb_c_cbcast(ictxt,n,v,root) bind(c)
use psb_base_mod, only : psb_bcast
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_ipk_), value :: ictxt,n, root
complex(c_float_complex) :: v(*)
if (n < 0) then
@ -198,7 +198,7 @@ contains
subroutine psb_c_zbcast(ictxt,n,v,root) bind(c)
use psb_base_mod
implicit none
integer(psb_c_ipk), value :: ictxt,n, root
integer(psb_c_ipk_), value :: ictxt,n, root
complex(c_double_complex) :: v(*)
if (n < 0) then
@ -213,7 +213,7 @@ contains
subroutine psb_c_hbcast(ictxt,v,root) bind(c)
use psb_base_mod, only : psb_bcast, psb_info, psb_ipk_
implicit none
integer(psb_c_ipk), value :: ictxt, root
integer(psb_c_ipk_), value :: ictxt, root
character(c_char) :: v(*)
integer(psb_ipk_) :: iam, np, n
@ -235,8 +235,8 @@ contains
use psb_base_string_cbind_mod
implicit none
character(c_char), intent(inout) :: cmesg(*)
integer(psb_c_ipk), intent(in), value :: len
integer(psb_c_ipk) :: res
integer(psb_c_ipk_), intent(in), value :: len
integer(psb_c_ipk_) :: res
character(len=psb_max_errmsg_len_), allocatable :: fmesg(:)
character(len=psb_max_errmsg_len_) :: tmp
integer :: i, j, ll, il

@ -8,14 +8,14 @@ contains
function psb_c_d_ovrl(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -39,15 +39,15 @@ contains
function psb_c_d_ovrl_opt(xh,cdh,update,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: update, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: update, mode
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -72,14 +72,14 @@ contains
function psb_c_d_halo(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -103,8 +103,8 @@ contains
function psb_c_d_halo_opt(xh,cdh,tran,data,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: data, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: data, mode
character(c_char) :: tran
@ -114,7 +114,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
character :: ftran
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -141,8 +141,8 @@ contains
function psb_c_d_vscatter(ng,gx,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_lpk), value :: ng
integer(psb_c_ipk_) :: res
integer(psb_c_lpk_), value :: ng
real(c_double), target :: gx(*)
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
@ -150,7 +150,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: vp
real(psb_dpk_), pointer :: pgx(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -175,7 +175,7 @@ contains
function psb_c_dvgather(v,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
real(c_double), target :: v(*)
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
@ -183,7 +183,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: vp
real(psb_dpk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -208,13 +208,13 @@ contains
function psb_c_dspgather(gah,ah,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: ah, gah
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap, gap
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
if (c_associated(cdh%item)) then

@ -8,7 +8,7 @@ contains
function psb_c_dgeaxpby(alpha,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh,yh
type(psb_c_descriptor) :: cdh
@ -16,7 +16,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -51,7 +51,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -78,7 +78,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -104,7 +104,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -132,7 +132,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -158,7 +158,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -183,7 +183,7 @@ contains
function psb_c_dspmm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: ah
type(psb_c_dvector) :: xh,yh
@ -192,7 +192,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp,yp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -225,7 +225,7 @@ contains
function psb_c_dspmm_opt(alpha,ah,xh,beta,yh,cdh,trans,doswap) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: ah
type(psb_c_dvector) :: xh,yh
@ -239,7 +239,7 @@ contains
type(psb_dspmat_type), pointer :: ap
character :: ftrans
logical :: fdoswap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -274,7 +274,7 @@ contains
function psb_c_dspsm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: ah
type(psb_c_dvector) :: xh,yh
@ -283,7 +283,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp,yp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then

@ -11,11 +11,11 @@ contains
function psb_c_dvect_get_nrows(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh
type(psb_d_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -29,13 +29,13 @@ contains
function psb_c_dvect_f_get_cpy(v,xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
real(c_double) :: v(*)
type(psb_c_dvector) :: xh
type(psb_d_vect_type), pointer :: vp
real(psb_dpk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -52,11 +52,11 @@ contains
function psb_c_dvect_zero(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh
type(psb_d_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -73,11 +73,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: mh
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -96,11 +96,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: mh
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -119,12 +119,12 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
character(c_char) :: name(*)
type(psb_c_dspmat) :: mh
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(1024) :: fname
res = 0

@ -11,13 +11,13 @@ contains
function psb_c_dgeall(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -40,13 +40,13 @@ contains
function psb_c_dgeasb(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -70,13 +70,13 @@ contains
function psb_c_dgefree(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -102,16 +102,16 @@ contains
function psb_c_dgeins(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
real(c_double) :: val(*)
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -143,16 +143,16 @@ contains
function psb_c_dgeins_add(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
real(c_double) :: val(*)
type(psb_c_dvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_d_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -183,13 +183,13 @@ contains
function psb_c_dspall(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -213,13 +213,13 @@ contains
function psb_c_dspasb(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -242,13 +242,13 @@ contains
function psb_c_dspfree(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -277,10 +277,10 @@ contains
use psb_d_rsb_mat_mod
#endif
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: cdh, mh,upd,dupl
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: cdh, mh,upd,dupl
character(c_char) :: afmt(*)
integer(psb_c_ipk) :: info,n, fdupl
integer(psb_c_ipk_) :: info,n, fdupl
character(len=5) :: fafmt
#ifdef HAVE_LIBRSB
type(psb_d_rsb_sparse_mat) :: arsb
@ -313,16 +313,16 @@ contains
function psb_c_dspins(nz,irw,icl,val,mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*), icl(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*), icl(*)
real(c_double) :: val(*)
type(psb_c_dspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: ixb,info,n
integer(psb_c_ipk_) :: ixb,info,n
res = -1
if (c_associated(cdh%item)) then
@ -350,14 +350,14 @@ contains
function psb_c_dsprn(mh,cdh,clear) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
logical(c_bool), value :: clear
type(psb_c_dspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
logical :: fclear
res = -1
@ -382,9 +382,9 @@ contains
!!$ function psb_c_dspprint(mh) bind(c) result(res)
!!$
!!$ implicit none
!!$ integer(psb_c_ipk) :: res
!!$ integer(psb_c_ipk), value :: mh
!!$ integer(psb_c_ipk) :: info
!!$ integer(psb_c_ipk_) :: res
!!$ integer(psb_c_ipk_), value :: mh
!!$ integer(psb_c_ipk_) :: info
!!$
!!$
!!$ res = -1

@ -8,14 +8,14 @@ contains
function psb_c_s_ovrl(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -39,15 +39,15 @@ contains
function psb_c_s_ovrl_opt(xh,cdh,update,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: update, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: update, mode
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -72,14 +72,14 @@ contains
function psb_c_s_halo(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -103,8 +103,8 @@ contains
function psb_c_s_halo_opt(xh,cdh,tran,data,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: data, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: data, mode
character(c_char) :: tran
@ -114,7 +114,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
character :: ftran
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -141,8 +141,8 @@ contains
function psb_c_s_vscatter(ng,gx,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_lpk), value :: ng
integer(psb_c_ipk_) :: res
integer(psb_c_lpk_), value :: ng
real(c_float), target :: gx(*)
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
@ -150,7 +150,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: vp
real(psb_spk_), pointer :: pgx(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -175,7 +175,7 @@ contains
function psb_c_svgather(v,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
real(c_float), target :: v(*)
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
@ -183,7 +183,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: vp
real(psb_spk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -208,13 +208,13 @@ contains
function psb_c_sspgather(gah,ah,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: ah, gah
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap, gap
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
if (c_associated(cdh%item)) then

@ -8,7 +8,7 @@ contains
function psb_c_sgeaxpby(alpha,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh,yh
type(psb_c_descriptor) :: cdh
@ -16,7 +16,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -51,7 +51,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -78,7 +78,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -104,7 +104,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -132,7 +132,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -158,7 +158,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -183,7 +183,7 @@ contains
function psb_c_sspmm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: ah
type(psb_c_svector) :: xh,yh
@ -192,7 +192,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp,yp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -225,7 +225,7 @@ contains
function psb_c_sspmm_opt(alpha,ah,xh,beta,yh,cdh,trans,doswap) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: ah
type(psb_c_svector) :: xh,yh
@ -239,7 +239,7 @@ contains
type(psb_sspmat_type), pointer :: ap
character :: ftrans
logical :: fdoswap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -274,7 +274,7 @@ contains
function psb_c_sspsm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: ah
type(psb_c_svector) :: xh,yh
@ -283,7 +283,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp,yp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then

@ -11,11 +11,11 @@ contains
function psb_c_svect_get_nrows(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh
type(psb_s_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -29,13 +29,13 @@ contains
function psb_c_svect_f_get_cpy(v,xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
real(c_float) :: v(*)
type(psb_c_svector) :: xh
type(psb_s_vect_type), pointer :: vp
real(psb_spk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -52,11 +52,11 @@ contains
function psb_c_svect_zero(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh
type(psb_s_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -73,11 +73,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: mh
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -96,11 +96,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: mh
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -119,12 +119,12 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
character(c_char) :: name(*)
type(psb_c_sspmat) :: mh
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(1024) :: fname
res = 0

@ -11,13 +11,13 @@ contains
function psb_c_sgeall(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -40,13 +40,13 @@ contains
function psb_c_sgeasb(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -70,13 +70,13 @@ contains
function psb_c_sgefree(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -102,16 +102,16 @@ contains
function psb_c_sgeins(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
real(c_float) :: val(*)
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -143,16 +143,16 @@ contains
function psb_c_sgeins_add(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
real(c_float) :: val(*)
type(psb_c_svector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_s_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -183,13 +183,13 @@ contains
function psb_c_sspall(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -213,13 +213,13 @@ contains
function psb_c_sspasb(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -242,13 +242,13 @@ contains
function psb_c_sspfree(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -277,10 +277,10 @@ contains
use psb_s_rsb_mat_mod
#endif
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: cdh, mh,upd,dupl
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: cdh, mh,upd,dupl
character(c_char) :: afmt(*)
integer(psb_c_ipk) :: info,n, fdupl
integer(psb_c_ipk_) :: info,n, fdupl
character(len=5) :: fafmt
#ifdef HAVE_LIBRSB
type(psb_s_rsb_sparse_mat) :: arsb
@ -313,16 +313,16 @@ contains
function psb_c_sspins(nz,irw,icl,val,mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*), icl(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*), icl(*)
real(c_float) :: val(*)
type(psb_c_sspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: ixb,info,n
integer(psb_c_ipk_) :: ixb,info,n
res = -1
if (c_associated(cdh%item)) then
@ -350,14 +350,14 @@ contains
function psb_c_ssprn(mh,cdh,clear) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
logical(c_bool), value :: clear
type(psb_c_sspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
logical :: fclear
res = -1
@ -382,9 +382,9 @@ contains
!!$ function psb_c_sspprint(mh) bind(c) result(res)
!!$
!!$ implicit none
!!$ integer(psb_c_ipk) :: res
!!$ integer(psb_c_ipk), value :: mh
!!$ integer(psb_c_ipk) :: info
!!$ integer(psb_c_ipk_) :: res
!!$ integer(psb_c_ipk_), value :: mh
!!$ integer(psb_c_ipk_) :: info
!!$
!!$
!!$ res = -1

@ -8,14 +8,14 @@ contains
function psb_c_z_ovrl(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -39,15 +39,15 @@ contains
function psb_c_z_ovrl_opt(xh,cdh,update,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: update, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: update, mode
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -72,14 +72,14 @@ contains
function psb_c_z_halo(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -103,8 +103,8 @@ contains
function psb_c_z_halo_opt(xh,cdh,tran,data,mode) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: data, mode
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: data, mode
character(c_char) :: tran
@ -114,7 +114,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
character :: ftran
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -141,8 +141,8 @@ contains
function psb_c_z_vscatter(ng,gx,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_lpk), value :: ng
integer(psb_c_ipk_) :: res
integer(psb_c_lpk_), value :: ng
complex(c_double_complex), target :: gx(*)
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
@ -150,7 +150,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: vp
complex(psb_dpk_), pointer :: pgx(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -175,7 +175,7 @@ contains
function psb_c_zvgather(v,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
complex(c_double_complex), target :: v(*)
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
@ -183,7 +183,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: vp
complex(psb_dpk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -208,13 +208,13 @@ contains
function psb_c_zspgather(gah,ah,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: ah, gah
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap, gap
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
if (c_associated(cdh%item)) then

@ -8,7 +8,7 @@ contains
function psb_c_zgeaxpby(alpha,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh,yh
type(psb_c_descriptor) :: cdh
@ -16,7 +16,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -51,7 +51,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -78,7 +78,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -104,7 +104,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
@ -132,7 +132,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -158,7 +158,7 @@ contains
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp,yp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1.0
if (c_associated(cdh%item)) then
@ -183,7 +183,7 @@ contains
function psb_c_zspmm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: ah
type(psb_c_zvector) :: xh,yh
@ -192,7 +192,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp,yp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -225,7 +225,7 @@ contains
function psb_c_zspmm_opt(alpha,ah,xh,beta,yh,cdh,trans,doswap) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: ah
type(psb_c_zvector) :: xh,yh
@ -239,7 +239,7 @@ contains
type(psb_zspmat_type), pointer :: ap
character :: ftrans
logical :: fdoswap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then
@ -274,7 +274,7 @@ contains
function psb_c_zspsm(alpha,ah,xh,beta,yh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: ah
type(psb_c_zvector) :: xh,yh
@ -283,7 +283,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp,yp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(cdh%item)) then

@ -11,11 +11,11 @@ contains
function psb_c_zvect_get_nrows(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh
type(psb_z_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -29,13 +29,13 @@ contains
function psb_c_zvect_f_get_cpy(v,xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
complex(c_double_complex) :: v(*)
type(psb_c_zvector) :: xh
type(psb_z_vect_type), pointer :: vp
complex(psb_dpk_), allocatable :: fv(:)
integer(psb_c_ipk) :: info, sz
integer(psb_c_ipk_) :: info, sz
res = -1
@ -52,11 +52,11 @@ contains
function psb_c_zvect_zero(xh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh
type(psb_z_vect_type), pointer :: vp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -73,11 +73,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: mh
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -96,11 +96,11 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: mh
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = 0
if (c_associated(mh%item)) then
@ -119,12 +119,12 @@ contains
use psb_objhandle_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
character(c_char) :: name(*)
type(psb_c_zspmat) :: mh
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(1024) :: fname
res = 0

@ -11,13 +11,13 @@ contains
function psb_c_zgeall(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -40,13 +40,13 @@ contains
function psb_c_zgeasb(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -70,13 +70,13 @@ contains
function psb_c_zgefree(xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
@ -102,16 +102,16 @@ contains
function psb_c_zgeins(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
complex(c_double_complex) :: val(*)
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -143,16 +143,16 @@ contains
function psb_c_zgeins_add(nz,irw,val,xh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*)
complex(c_double_complex) :: val(*)
type(psb_c_zvector) :: xh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_z_vect_type), pointer :: xp
integer(psb_c_ipk) :: ixb, info
integer(psb_c_ipk_) :: ixb, info
res = -1
if (c_associated(cdh%item)) then
@ -183,13 +183,13 @@ contains
function psb_c_zspall(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -213,13 +213,13 @@ contains
function psb_c_zspasb(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -242,13 +242,13 @@ contains
function psb_c_zspfree(mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info,n
integer(psb_c_ipk_) :: info,n
res = -1
if (c_associated(cdh%item)) then
@ -277,10 +277,10 @@ contains
use psb_z_rsb_mat_mod
#endif
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: cdh, mh,upd,dupl
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: cdh, mh,upd,dupl
character(c_char) :: afmt(*)
integer(psb_c_ipk) :: info,n, fdupl
integer(psb_c_ipk_) :: info,n, fdupl
character(len=5) :: fafmt
#ifdef HAVE_LIBRSB
type(psb_z_rsb_sparse_mat) :: arsb
@ -313,16 +313,16 @@ contains
function psb_c_zspins(nz,irw,icl,val,mh,cdh) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: nz
integer(psb_c_lpk) :: irw(*), icl(*)
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: nz
integer(psb_c_lpk_) :: irw(*), icl(*)
complex(c_double_complex) :: val(*)
type(psb_c_zspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: ixb,info,n
integer(psb_c_ipk_) :: ixb,info,n
res = -1
if (c_associated(cdh%item)) then
@ -350,14 +350,14 @@ contains
function psb_c_zsprn(mh,cdh,clear) bind(c) result(res)
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
logical(c_bool), value :: clear
type(psb_c_zspmat) :: mh
type(psb_c_descriptor) :: cdh
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
logical :: fclear
res = -1
@ -382,9 +382,9 @@ contains
!!$ function psb_c_zspprint(mh) bind(c) result(res)
!!$
!!$ implicit none
!!$ integer(psb_c_ipk) :: res
!!$ integer(psb_c_ipk), value :: mh
!!$ integer(psb_c_ipk) :: info
!!$ integer(psb_c_ipk_) :: res
!!$ integer(psb_c_ipk_), value :: mh
!!$ integer(psb_c_ipk_) :: info
!!$
!!$
!!$ res = -1

@ -4,7 +4,7 @@ module psb_base_krylov_cbind_mod
use psb_objhandle_mod
type, bind(c) :: solveroptions
integer(psb_c_ipk) :: iter, itmax, itrace, irst, istop
integer(psb_c_ipk_) :: iter, itmax, itrace, irst, istop
real(c_double) :: eps, err
end type solveroptions
@ -14,7 +14,7 @@ contains
& bind(c,name='psb_c_DefaultSolverOptions') result(res)
implicit none
type(solveroptions) :: options
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
options%itmax = 1000
options%itrace = 0

@ -13,7 +13,7 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_cprec) :: ph
@ -38,14 +38,14 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_cprec) :: ph
type(psb_c_cvector) :: bh,xh
integer(psb_c_ipk), value :: itmax,itrace,irst,istop
integer(psb_c_ipk_), value :: itmax,itrace,irst,istop
real(c_double), value :: eps
integer(psb_c_ipk) :: iter
integer(psb_c_ipk_) :: iter
real(c_double) :: err
character(c_char) :: methd(*)
type(solveroptions) :: options
@ -54,7 +54,7 @@ contains
type(psb_cprec_type), pointer :: precp
type(psb_c_vect_type), pointer :: xp, bp
integer(psb_c_ipk) :: info,fitmax,fitrace,first,fistop,fiter
integer(psb_c_ipk_) :: info,fitmax,fitrace,first,fistop,fiter
character(len=20) :: fmethd
real(psb_spk_) :: feps,ferr

@ -13,7 +13,7 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_dprec) :: ph
@ -38,14 +38,14 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_dprec) :: ph
type(psb_c_dvector) :: bh,xh
integer(psb_c_ipk), value :: itmax,itrace,irst,istop
integer(psb_c_ipk_), value :: itmax,itrace,irst,istop
real(c_double), value :: eps
integer(psb_c_ipk) :: iter
integer(psb_c_ipk_) :: iter
real(c_double) :: err
character(c_char) :: methd(*)
type(solveroptions) :: options
@ -54,7 +54,7 @@ contains
type(psb_dprec_type), pointer :: precp
type(psb_d_vect_type), pointer :: xp, bp
integer(psb_c_ipk) :: info,fitmax,fitrace,first,fistop,fiter
integer(psb_c_ipk_) :: info,fitmax,fitrace,first,fistop,fiter
character(len=20) :: fmethd
real(psb_dpk_) :: feps,ferr

@ -13,7 +13,7 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_sprec) :: ph
@ -38,14 +38,14 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_sprec) :: ph
type(psb_c_svector) :: bh,xh
integer(psb_c_ipk), value :: itmax,itrace,irst,istop
integer(psb_c_ipk_), value :: itmax,itrace,irst,istop
real(c_double), value :: eps
integer(psb_c_ipk) :: iter
integer(psb_c_ipk_) :: iter
real(c_double) :: err
character(c_char) :: methd(*)
type(solveroptions) :: options
@ -54,7 +54,7 @@ contains
type(psb_sprec_type), pointer :: precp
type(psb_s_vect_type), pointer :: xp, bp
integer(psb_c_ipk) :: info,fitmax,fitrace,first,fistop,fiter
integer(psb_c_ipk_) :: info,fitmax,fitrace,first,fistop,fiter
character(len=20) :: fmethd
real(psb_spk_) :: feps,ferr

@ -13,7 +13,7 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_zprec) :: ph
@ -38,14 +38,14 @@ contains
use psb_prec_cbind_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: ah
type(psb_c_descriptor) :: cdh
type(psb_c_zprec) :: ph
type(psb_c_zvector) :: bh,xh
integer(psb_c_ipk), value :: itmax,itrace,irst,istop
integer(psb_c_ipk_), value :: itmax,itrace,irst,istop
real(c_double), value :: eps
integer(psb_c_ipk) :: iter
integer(psb_c_ipk_) :: iter
real(c_double) :: err
character(c_char) :: methd(*)
type(solveroptions) :: options
@ -54,7 +54,7 @@ contains
type(psb_zprec_type), pointer :: precp
type(psb_z_vect_type), pointer :: xp, bp
integer(psb_c_ipk) :: info,fitmax,fitrace,first,fistop,fiter
integer(psb_c_ipk_) :: info,fitmax,fitrace,first,fistop,fiter
character(len=20) :: fmethd
real(psb_dpk_) :: feps,ferr

@ -18,13 +18,13 @@ contains
use psb_prec_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: ictxt
type(psb_c_cprec) :: ph
character(c_char) :: ptype(*)
type(psb_cprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(len=80) :: fptype
res = -1
@ -53,7 +53,7 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cspmat) :: ah
type(psb_c_cprec) :: ph
type(psb_c_descriptor) :: cdh
@ -61,7 +61,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_cspmat_type), pointer :: ap
type(psb_cprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
!!$ write(*,*) 'Entry: ', psb_c_cd_get_local_rows(cdh)
@ -95,10 +95,10 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_cprec) :: ph
type(psb_cprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(ph%item)) then

@ -18,13 +18,13 @@ contains
use psb_prec_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: ictxt
type(psb_c_dprec) :: ph
character(c_char) :: ptype(*)
type(psb_dprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(len=80) :: fptype
res = -1
@ -53,7 +53,7 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dspmat) :: ah
type(psb_c_dprec) :: ph
type(psb_c_descriptor) :: cdh
@ -61,7 +61,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_dspmat_type), pointer :: ap
type(psb_dprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
!!$ write(*,*) 'Entry: ', psb_c_cd_get_local_rows(cdh)
@ -95,10 +95,10 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_dprec) :: ph
type(psb_dprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(ph%item)) then

@ -18,13 +18,13 @@ contains
use psb_prec_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: ictxt
type(psb_c_sprec) :: ph
character(c_char) :: ptype(*)
type(psb_sprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(len=80) :: fptype
res = -1
@ -53,7 +53,7 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sspmat) :: ah
type(psb_c_sprec) :: ph
type(psb_c_descriptor) :: cdh
@ -61,7 +61,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_sspmat_type), pointer :: ap
type(psb_sprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
!!$ write(*,*) 'Entry: ', psb_c_cd_get_local_rows(cdh)
@ -95,10 +95,10 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_sprec) :: ph
type(psb_sprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(ph%item)) then

@ -18,13 +18,13 @@ contains
use psb_prec_mod
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk), value :: ictxt
integer(psb_c_ipk_) :: res
integer(psb_c_ipk_), value :: ictxt
type(psb_c_zprec) :: ph
character(c_char) :: ptype(*)
type(psb_zprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
character(len=80) :: fptype
res = -1
@ -53,7 +53,7 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zspmat) :: ah
type(psb_c_zprec) :: ph
type(psb_c_descriptor) :: cdh
@ -61,7 +61,7 @@ contains
type(psb_desc_type), pointer :: descp
type(psb_zspmat_type), pointer :: ap
type(psb_zprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
!!$ write(*,*) 'Entry: ', psb_c_cd_get_local_rows(cdh)
@ -95,10 +95,10 @@ contains
use psb_base_string_cbind_mod
implicit none
integer(psb_c_ipk) :: res
integer(psb_c_ipk_) :: res
type(psb_c_zprec) :: ph
type(psb_zprec_type), pointer :: precp
integer(psb_c_ipk) :: info
integer(psb_c_ipk_) :: info
res = -1
if (c_associated(ph%item)) then

Loading…
Cancel
Save