psblas3-integer8:

base/modules/psb_c_linmap_mod.f90
 base/modules/psb_d_linmap_mod.f90
 base/modules/psb_desc_type.f90
 base/modules/psb_error_impl.F90
 base/modules/psb_error_mod.F90
 base/modules/psb_gen_block_map_mod.f90
 base/modules/psb_glist_map_mod.f90
 base/modules/psb_hash_map_mod.f90
 base/modules/psb_hash_mod.f90
 base/modules/psb_indx_map_mod.f90
 base/modules/psb_list_map_mod.f90
 base/modules/psb_repl_map_mod.f90
 base/modules/psb_s_linmap_mod.f90
 base/modules/psb_z_linmap_mod.f90
 base/modules/psi_bcast_mod.F90
 base/modules/psi_i_mod.f90

After the fix to psi_reduce, all the other stuff in base/modules works
with 4 bytes. Need to cross-check compilation on 8-bytes.
psblas3-type-indexed
Salvatore Filippone 13 years ago
parent e2f247f1ea
commit 8cf8d5a4bc

@ -36,13 +36,13 @@
! to different spaces.
!
module psb_c_linmap_mod
use psb_const_mod
use psb_c_mat_mod, only : psb_cspmat_type
use psb_descriptor_type, only : psb_desc_type
use psb_base_linmap_mod
type, extends(psb_base_linmap_type) :: psb_clinmap_type
type(psb_cspmat_type) :: map_X2Y, map_Y2X
contains
@ -75,7 +75,7 @@ module psb_c_linmap_mod
integer(psb_ipk_), intent(out) :: info
complex(psb_spk_), optional :: work(:)
end subroutine psb_c_map_X2Y_vect
end interface
end interface psb_map_X2Y
interface psb_map_Y2X
subroutine psb_c_map_Y2X(alpha,x,beta,y,map,info,work)
@ -100,20 +100,20 @@ module psb_c_linmap_mod
integer(psb_ipk_), intent(out) :: info
complex(psb_spk_), optional :: work(:)
end subroutine psb_c_map_Y2X_vect
end interface
end interface psb_map_Y2X
interface psb_map_cscnv
module procedure psb_c_map_cscnv
end interface
end interface psb_map_cscnv
interface psb_linmap_sub
module procedure psb_c_linmap_sub
end interface
end interface psb_linmap_sub
interface psb_move_alloc
module procedure psb_clinmap_transfer
end interface
end interface psb_move_alloc
interface psb_linmap
function psb_c_linmap(map_kind,desc_X, desc_Y, map_X2Y, map_Y2X,iaggr,naggr)
@ -126,7 +126,7 @@ module psb_c_linmap_mod
integer(psb_ipk_), intent(in) :: map_kind
integer(psb_ipk_), intent(in), optional :: iaggr(:), naggr(:)
end function psb_c_linmap
end interface
end interface psb_linmap
private :: c_map_sizeof, c_is_asb, c_free

@ -132,8 +132,6 @@ module psb_d_linmap_mod
contains
function d_map_sizeof(map) result(val)

@ -890,7 +890,7 @@ contains
Do j=0,n_elem_recv-1
idx = idxlist(incnt+psb_elem_recv_+j)
call psb_ensure_size((outcnt+3),tmp,info,pad=-1)
call psb_ensure_size((outcnt+3),tmp,info,pad=-ione)
if (info /= psb_success_) then
info=psb_err_from_subroutine_
call psb_errpush(info,name,a_err='psb_ensure_size')

@ -2,7 +2,7 @@
subroutine psb_errcomm(ictxt, err)
use psb_error_mod, psb_protect_name => psb_errcomm
use psb_penv_mod
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(inout):: err
integer(psb_ipk_) :: temp(2)
@ -53,12 +53,12 @@ subroutine psb_perror(ictxt)
use psb_error_mod
use psb_penv_mod
implicit none
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_) :: err_c
character(len=20) :: r_name
character(len=40) :: a_e_d
integer(psb_ipk_) :: i_e_d(5)
integer(psb_ipk_) :: iam, np
integer(psb_mpik_) :: iam, np
call psb_info(ictxt,iam,np)

@ -60,19 +60,28 @@ module psb_error_mod
subroutine psb_serror()
end subroutine psb_serror
subroutine psb_perror(ictxt)
import :: psb_ipk_
integer(psb_ipk_), intent(in) :: ictxt
import :: psb_mpik_
integer(psb_mpik_), intent(in) :: ictxt
end subroutine psb_perror
end interface
interface
subroutine psb_errcomm(ictxt, err)
import :: psb_ipk_
integer(psb_ipk_), intent(in) :: ictxt
import :: psb_mpik_, psb_ipk_
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(inout):: err
end subroutine psb_errcomm
end interface
#if defined(LONG_INTEGERS)
interface psb_error
module procedure psb_perror_ipk
end interface psb_error
interface psb_errcomm
module procedure psb_errcomm_ipk
end interface psb_errcomm
#endif
private
@ -112,7 +121,22 @@ module psb_error_mod
contains
#if defined(LONG_INTEGERS)
subroutine psb_errcomm_ipk(ictxt, err)
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_ipk_), intent(inout):: err
integer(psb_mpik_) :: iictxt
iictxt = ictxt
call psb_errcomm(iictxt,err)
end subroutine psb_errcomm_ipk
subroutine psb_perror_ipk(ictxt)
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_) :: iictxt
iictxt = ictxt
call psb_perror(iictxt)
end subroutine psb_perror_ipk
#endif
! saves action to support error traceback
! also changes error action to "return"
subroutine psb_erractionsave(err_act)
@ -330,7 +354,7 @@ contains
character(len=20), intent(in) :: r_name
character(len=40), intent(in) :: a_e_d
integer(psb_ipk_), intent(in) :: i_e_d(5)
integer(psb_ipk_), optional :: me
integer(psb_mpik_), optional :: me
if(present(me)) then
write(psb_err_unit,&

@ -89,6 +89,7 @@ module psb_gen_block_map_mod
& block_g2lv2, block_g2ls1_ins, block_g2ls2_ins,&
& block_g2lv1_ins, block_g2lv2_ins, block_clone
integer(psb_ipk_), private :: laddsz=500
contains
@ -284,7 +285,7 @@ contains
logical, intent(in), optional :: mask(:)
logical, intent(in), optional :: owned
integer(psb_ipk_) :: i, nv, is
integer(psb_ipk_) :: ictxt, iam, np
integer(psb_mpik_) :: ictxt, iam, np
logical :: owned_
info = 0
@ -476,7 +477,7 @@ contains
ix = psb_issrch(idx(i),nv,idxmap%loc_to_glob)
if (ix < 0) then
ix = idxmap%local_cols + 1
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=500)
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=laddsz)
if (info /= 0) then
info = -4
return
@ -505,7 +506,7 @@ contains
ix = psb_issrch(idx(i),nv,idxmap%loc_to_glob)
if (ix < 0) then
ix = idxmap%local_cols + 1
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=500)
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=laddsz)
if (info /= 0) then
info = -4
return
@ -582,10 +583,12 @@ contains
use psb_error_mod
implicit none
class(psb_gen_block_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(in) :: ictxt, nl
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(in) :: nl
integer(psb_ipk_), intent(out) :: info
! To be implemented
integer(psb_ipk_) :: iam, np, i, ntot
integer(psb_mpik_) :: iam, np
integer(psb_ipk_) :: i, ntot
integer(psb_ipk_), allocatable :: vnl(:)
info = 0
@ -644,7 +647,8 @@ contains
class(psb_gen_block_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: nhal, ictxt, iam, np
integer(psb_ipk_) :: nhal
integer(psb_mpik_) :: ictxt, iam, np
info = 0
ictxt = idxmap%get_ctxt()

@ -96,10 +96,12 @@ contains
use psb_error_mod
implicit none
class(psb_glist_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(in) :: ictxt, vg(:)
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(in) :: vg(:)
integer(psb_ipk_), intent(out) :: info
! To be implemented
integer(psb_ipk_) :: iam, np, i, n, nl
integer(psb_mpik_) :: iam, np
integer(psb_ipk_) :: i, n, nl
info = 0
@ -155,7 +157,8 @@ contains
integer(psb_ipk_), allocatable, intent(out) :: iprc(:)
class(psb_glist_map), intent(in) :: idxmap
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: ictxt, iam, np, nv, i, ngp
integer(psb_mpik_) :: ictxt, iam, np
integer(psb_ipk_) :: nv, i, ngp
ictxt = idxmap%get_ctxt()
call psb_info(ictxt,iam,np)

File diff suppressed because it is too large Load Diff

@ -130,7 +130,8 @@ contains
subroutine HashFree(hashin,info)
use psb_realloc_mod
type(psb_hash_type) :: hashin
integer(psb_ipk_) :: info
info = psb_success_
if (allocated(hashin%table)) then
deallocate(hashin%table,stat=info)

@ -89,8 +89,8 @@ module psb_indx_map_mod
type :: psb_indx_map
integer(psb_ipk_) :: state = psb_desc_null_
integer(psb_ipk_) :: ictxt = -1
integer(psb_ipk_) :: mpic = -1
integer(psb_mpik_) :: ictxt = -1
integer(psb_mpik_) :: mpic = -1
integer(psb_ipk_) :: global_rows = -1
integer(psb_ipk_) :: global_cols = -1
integer(psb_ipk_) :: local_rows = -1
@ -241,7 +241,7 @@ contains
function base_get_ctxt(idxmap) result(val)
implicit none
class(psb_indx_map), intent(in) :: idxmap
integer(psb_ipk_) :: val
integer(psb_mpik_) :: val
val = idxmap%ictxt
@ -251,7 +251,7 @@ contains
function base_get_mpic(idxmap) result(val)
implicit none
class(psb_indx_map), intent(in) :: idxmap
integer(psb_ipk_) :: val
integer(psb_mpik_) :: val
val = idxmap%mpic
@ -269,7 +269,7 @@ contains
subroutine base_set_ctxt(idxmap,val)
implicit none
class(psb_indx_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(in) :: val
integer(psb_mpik_), intent(in) :: val
idxmap%ictxt = val
end subroutine base_set_ctxt
@ -309,7 +309,7 @@ contains
subroutine base_set_mpic(idxmap,val)
implicit none
class(psb_indx_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(in) :: val
integer(psb_mpik_), intent(in) :: val
idxmap%mpic = val
end subroutine base_set_mpic
@ -773,7 +773,8 @@ contains
use psb_error_mod
implicit none
class(psb_indx_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(in) :: ictxt, vl(:)
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(in) :: vl(:)
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
character(len=20) :: name='base_init_vl'

@ -80,6 +80,8 @@ module psb_list_map_mod
& list_g2lv2, list_g2ls1_ins, list_g2ls2_ins,&
& list_g2lv1_ins, list_g2lv2_ins, list_row_extendable
integer(psb_ipk_), private :: laddsz=500
contains
function list_row_extendable() result(val)
@ -417,7 +419,7 @@ contains
ix = idxmap%glob_to_loc(idx(i))
if (ix < 0) then
ix = idxmap%local_cols + 1
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=500)
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=laddsz)
if (info /= 0) then
info = -4
return
@ -440,7 +442,7 @@ contains
ix = idxmap%glob_to_loc(idx(i))
if (ix < 0) then
ix = idxmap%local_cols + 1
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=500)
call psb_ensure_size(ix,idxmap%loc_to_glob,info,addsz=laddsz)
if (info /= 0) then
info = -4
return
@ -544,10 +546,12 @@ contains
use psb_error_mod
implicit none
class(psb_list_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(in) :: ictxt, vl(:)
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(in) :: vl(:)
integer(psb_ipk_), intent(out) :: info
! To be implemented
integer(psb_ipk_) :: iam, np, i, ix, nl, n, nrt
integer(psb_ipk_) :: i, ix, nl, n, nrt
integer(psb_mpik_) :: iam, np
info = 0
call psb_info(ictxt,iam,np)
@ -610,7 +614,8 @@ contains
class(psb_list_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: nhal, ictxt, iam, np
integer(psb_ipk_) :: nhal
integer(psb_mpik_) :: ictxt, iam, np
info = 0
ictxt = idxmap%get_ctxt()

@ -459,7 +459,8 @@ contains
integer(psb_ipk_), allocatable, intent(out) :: iprc(:)
class(psb_repl_map), intent(in) :: idxmap
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: ictxt, iam, np, nv
integer(psb_ipk_) :: nv
integer(psb_mpik_) :: ictxt, iam, np
ictxt = idxmap%get_ctxt()
call psb_info(ictxt,iam,np)
@ -480,10 +481,11 @@ contains
use psb_error_mod
implicit none
class(psb_repl_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(in) :: ictxt, nl
integer(psb_ipk_), intent(in) :: nl
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(out) :: info
! To be implemented
integer(psb_ipk_) :: iam, np
integer(psb_mpik_) :: iam, np
info = 0
call psb_info(ictxt,iam,np)
@ -513,7 +515,7 @@ contains
class(psb_repl_map), intent(inout) :: idxmap
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: ictxt, iam, np
integer(psb_mpik_) :: ictxt, iam, np
info = 0
ictxt = idxmap%get_ctxt()

@ -132,8 +132,6 @@ module psb_s_linmap_mod
contains
function s_map_sizeof(map) result(val)

@ -131,9 +131,6 @@ module psb_z_linmap_mod
private :: z_map_sizeof, z_is_asb, z_free
contains
function z_map_sizeof(map) result(val)

@ -29,11 +29,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(inout) :: dat
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -55,11 +55,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(inout) :: dat(:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
root_ = root
@ -80,11 +80,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
integer(psb_ipk_), intent(inout) :: dat(:,:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -107,11 +107,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
real(psb_spk_), intent(inout) :: dat
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -134,11 +134,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
real(psb_spk_), intent(inout) :: dat(:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -161,11 +161,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
real(psb_spk_), intent(inout) :: dat(:,:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -189,11 +189,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
real(psb_dpk_), intent(inout) :: dat
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -216,11 +216,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
real(psb_dpk_), intent(inout) :: dat(:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -242,11 +242,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
real(psb_dpk_), intent(inout) :: dat(:,:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -268,11 +268,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
complex(psb_spk_), intent(inout) :: dat
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -294,11 +294,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
complex(psb_spk_), intent(inout) :: dat(:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -320,11 +320,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
complex(psb_spk_), intent(inout) :: dat(:,:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -346,11 +346,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
complex(psb_dpk_), intent(inout) :: dat
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -372,11 +372,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
complex(psb_dpk_), intent(inout) :: dat(:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -398,11 +398,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
complex(psb_dpk_), intent(inout) :: dat(:,:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_, info
integer(psb_mpik_) :: iam, np, root_, info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -425,11 +425,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
character(len=*), intent(inout) :: dat
integer(psb_ipk_), intent(in), optional :: root,length
integer(psb_mpik_), intent(in), optional :: root,length
integer(psb_ipk_) :: iam, np, root_,length_,info
integer(psb_mpik_) :: iam, np, root_,length_,info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -458,11 +458,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
character(len=*), intent(inout) :: dat(:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_,length_,info, size_
integer(psb_mpik_) :: iam, np, root_,length_,info, size_
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -488,11 +488,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
logical, intent(inout) :: dat
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_,info
integer(psb_mpik_) :: iam, np, root_,info
#if !defined(SERIAL_MPI)
if (present(root)) then
@ -516,11 +516,11 @@ contains
#ifdef MPI_H
include 'mpif.h'
#endif
integer(psb_ipk_), intent(in) :: ictxt
integer(psb_mpik_), intent(in) :: ictxt
logical, intent(inout) :: dat(:)
integer(psb_ipk_), intent(in), optional :: root
integer(psb_mpik_), intent(in), optional :: root
integer(psb_ipk_) :: iam, np, root_,info
integer(psb_mpik_) :: iam, np, root_,info
#if !defined(SERIAL_MPI)
if (present(root)) then

@ -30,7 +30,7 @@
!!$
!!$
module psi_i_mod
use psb_descriptor_type, only : psb_desc_type, psb_ipk_
use psb_descriptor_type, only : psb_desc_type, psb_ipk_, psb_mpik_
interface
subroutine psi_compute_size(desc_data,&
@ -100,9 +100,10 @@ module psi_i_mod
interface
subroutine psi_extract_dep_list(ictxt,is_bld,is_upd,desc_str,dep_list,&
& length_dl,np,dl_lda,mode,info)
import :: psb_desc_type, psb_ipk_
import :: psb_desc_type, psb_ipk_, psb_mpik_
logical :: is_bld, is_upd
integer(psb_ipk_) :: ictxt,np,dl_lda,mode, info
integer(psb_mpik_) :: ictxt
integer(psb_ipk_) :: np,dl_lda,mode, info
integer(psb_ipk_) :: desc_str(*),dep_list(dl_lda,0:np),length_dl(0:np)
end subroutine psi_extract_dep_list
end interface

Loading…
Cancel
Save