psblas-3.99:

base/internals/psi_bld_tmphalo.f90
 base/internals/psi_crea_index.f90
 base/internals/psi_desc_index.F90
 base/internals/psi_fnd_owner.F90
 base/modules/psb_desc_mod.F90
 base/modules/psb_desc_mod.f90
 base/tools/psb_ccdbldext.F90
 base/tools/psb_cins.f90
 base/tools/psb_cspins.f90
 base/tools/psb_dcdbldext.F90
 base/tools/psb_dins.f90
 base/tools/psb_dspins.f90
 base/tools/psb_scdbldext.F90
 base/tools/psb_sins.f90
 base/tools/psb_sspins.f90
 base/tools/psb_zcdbldext.F90
 base/tools/psb_zins.f90
 base/tools/psb_zspins.f90
 test/fileread/cf_sample.f90
 test/fileread/df_sample.f90
 test/fileread/sf_sample.f90
 test/fileread/zf_sample.f90
 test/kernel/d_file_spmv.f90
 test/kernel/pdgenspmv.f90
 test/pargen/ppde2d.f90
 test/pargen/ppde3d.f90
 test/pargen/spde2d.f90
 test/pargen/spde3d.f90

Take out desc%indxmap% indirection where it makes sense.
psblas-3.2.0
Salvatore Filippone 11 years ago
parent eb9eeb0d4a
commit 799e126c67

@ -100,8 +100,8 @@ subroutine psi_bld_tmphalo(desc,info)
helem(i) = n_row+i ! desc%loc_to_glob(n_row+i)
end do
call desc%indxmap%l2gip(helem(1:nh),info)
call desc%indxmap%fnd_owner(helem(1:nh),hproc,info)
call desc%l2gip(helem(1:nh),info)
call desc%fnd_owner(helem(1:nh),hproc,info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,a_err='fnd_owner')

@ -81,7 +81,7 @@ subroutine psi_crea_index(desc_a,index_in,index_out,glob_idx,nxch,nsnd,nrcv,info
debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level()
ictxt = desc_a%indxmap%get_ctxt()
ictxt = desc_a%get_ctxt()
call psb_info(ictxt,me,np)
if (np == -1) then
@ -107,8 +107,8 @@ subroutine psi_crea_index(desc_a,index_in,index_out,glob_idx,nxch,nsnd,nrcv,info
& write(debug_unit,*) me,' ',trim(name),': calling extract_dep_list'
mode = 1
call psi_extract_dep_list(desc_a%indxmap%get_ctxt(),&
& desc_a%indxmap%is_bld(), desc_a%indxmap%is_upd(),&
call psi_extract_dep_list(ictxt,&
& desc_a%is_bld(), desc_a%is_upd(),&
& index_in, dep_list,length_dl,np,max(1,dl_lda),mode,info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,a_err='extrct_dl')

@ -145,8 +145,8 @@ subroutine psi_desc_index(desc,index_in,dep_list,&
debug_unit = psb_get_debug_unit()
debug_level = psb_get_debug_level()
ictxt = desc%indxmap%get_ctxt()
icomm = desc%indxmap%get_mpic()
ictxt = desc%get_context()
icomm = desc%get_mpic()
call psb_info(ictxt,me,np)
if (np == -1) then
info = psb_err_context_error_
@ -261,7 +261,7 @@ subroutine psi_desc_index(desc,index_in,dep_list,&
end do
else
call desc%indxmap%l2g(index_in(i+1:i+nerv),&
call desc%l2g(index_in(i+1:i+nerv),&
& sndbuf(bsdindx(proc+1)+1:bsdindx(proc+1)+nerv),&
& info)
@ -310,13 +310,13 @@ subroutine psi_desc_index(desc,index_in,dep_list,&
i = i + 1
nerv = sdsz(proc+1)
desc_index(i) = nerv
call desc%indxmap%g2l(sndbuf(bsdindx(proc+1)+1:bsdindx(proc+1)+nerv),&
call desc%g2l(sndbuf(bsdindx(proc+1)+1:bsdindx(proc+1)+nerv),&
& desc_index(i+1:i+nerv),info)
i = i + nerv + 1
nesd = rvsz(proc+1)
desc_index(i) = nesd
call desc%indxmap%g2l(rcvbuf(brvindx(proc+1)+1:brvindx(proc+1)+nesd),&
call desc%g2l(rcvbuf(brvindx(proc+1)+1:brvindx(proc+1)+nesd),&
& desc_index(i+1:i+nesd),info)
i = i + nesd + 1
end do

@ -109,10 +109,10 @@ subroutine psi_fnd_owner(nv,idx,iprc,desc,info)
goto 9999
end if
call desc%indxmap%fnd_owner(idx(1:nv),iprc,info)
call desc%fnd_owner(idx(1:nv),iprc,info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,a_err='indxmap%fnd_owner')
call psb_errpush(psb_err_from_subroutine_,name,a_err='desc%fnd_owner')
goto 9999
end if
call psb_erractionrestore(err_act)

@ -40,8 +40,6 @@ module psb_desc_mod
use psb_desc_const_mod
use psb_indx_map_mod
use psb_i_vect_mod
!!$
!!$ use psb_hash_mod
implicit none
@ -228,6 +226,7 @@ module psb_desc_mod
procedure, pass(desc) :: get_mpic => psb_cd_get_mpic
procedure, pass(desc) :: get_dectype => psb_cd_get_dectype
procedure, pass(desc) :: get_context => psb_cd_get_context
procedure, pass(desc) :: get_ctxt => psb_cd_get_context
procedure, pass(desc) :: get_local_rows => psb_cd_get_local_rows
procedure, pass(desc) :: get_local_cols => psb_cd_get_local_cols
procedure, pass(desc) :: get_global_rows => psb_cd_get_global_rows
@ -243,6 +242,7 @@ module psb_desc_mod
procedure, pass(desc) :: nullify => nullify_desc
procedure, pass(desc) :: get_fmt => cd_get_fmt
procedure, pass(desc) :: fnd_owner => cd_fnd_owner
procedure, pass(desc) :: l2gs1 => cd_l2gs1
procedure, pass(desc) :: l2gs2 => cd_l2gs2
procedure, pass(desc) :: l2gv1 => cd_l2gv1
@ -293,7 +293,7 @@ module psb_desc_mod
private :: nullify_desc, cd_get_fmt,&
& cd_l2gs1, cd_l2gs2, cd_l2gv1, cd_l2gv2, cd_g2ls1,&
& cd_g2ls2, cd_g2lv1, cd_g2lv2, cd_g2ls1_ins,&
& cd_g2ls2_ins, cd_g2lv1_ins, cd_g2lv2_ins
& cd_g2ls2_ins, cd_g2lv1_ins, cd_g2lv2_ins, cd_fnd_owner
integer(psb_ipk_), private, save :: cd_large_threshold=psb_default_large_threshold
@ -1566,4 +1566,44 @@ contains
end subroutine cd_g2lv2_ins
subroutine cd_fnd_owner(idx,iprc,desc,info)
use psb_error_mod
implicit none
integer(psb_ipk_), intent(in) :: idx(:)
integer(psb_ipk_), allocatable, intent(out) :: iprc(:)
class(psb_desc_type), intent(in) :: desc
integer(psb_ipk_), intent(out) :: info
integer(psb_ipk_) :: err_act
character(len=20) :: name='cd_fnd_owner'
logical, parameter :: debug=.false.
info = psb_success_
call psb_erractionsave(err_act)
if (allocated(desc%indxmap)) then
call desc%indxmap%fnd_owner(idx,iprc,info)
else
info = psb_err_invalid_cd_state_
end if
if (info /= psb_success_) then
call psb_errpush(info,name)
goto 9999
end if
call psb_erractionrestore(err_act)
return
9999 continue
call psb_erractionrestore(err_act)
if (err_act == psb_act_abort_) then
call psb_error()
return
end if
Return
end subroutine cd_fnd_owner
end module psb_desc_mod

File diff suppressed because it is too large Load Diff

@ -259,7 +259,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_recv-1
idx = ovrlap(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -360,7 +360,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype)
end If
idx = halo(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -404,7 +404,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_send-1
idx = halo(counter+psb_elem_send_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -440,7 +440,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype)
call psb_errpush(info,name,a_err='psb_ensure_size')
goto 9999
end if
call desc_ov%indxmap%l2g(icol(1:n_elem),&
call desc_ov%l2g(icol(1:n_elem),&
& works(idxs+tot_elem+1:idxs+tot_elem+n_elem),&
& info)
@ -529,7 +529,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype)
& write(debug_unit,*) me,' ',trim(name),&
& ': going for first idx_cnv', desc_ov%indxmap%get_state()
call desc_ov%indxmap%g2l(workr(1:iszr),maskr(1:iszr),info)
call desc_ov%g2l(workr(1:iszr),maskr(1:iszr),info)
iszs = count(maskr(1:iszr)<=0)
if (iszs > size(works)) call psb_realloc(iszs,works,info)
j = 0
@ -549,7 +549,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&
& ': going for fnd_owner', desc_ov%indxmap%get_state()
call desc_a%indxmap%fnd_owner(works(1:iszs),temp,info)
call desc_a%fnd_owner(works(1:iszs),temp,info)
n_col = desc_ov%get_local_cols()
if (debug_level >= psb_debug_outer_) &
@ -559,7 +559,7 @@ Subroutine psb_ccdbldext(a,desc_a,novr,desc_ov,info, extype)
do i=1,iszs
idx = works(i)
n_col = desc_ov%get_local_cols()
call desc_ov%indxmap%g2l_ins(idx,lidx,info)
call desc_ov%g2l_ins(idx,lidx,info)
if (desc_ov%get_local_cols() > n_col ) then
!
! This is a new index. Assigning a local index as

@ -134,7 +134,7 @@ subroutine psb_cinsvi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)
case(psb_dupl_ovwrt_)
@ -280,7 +280,7 @@ subroutine psb_cins_vect(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
call x%ins(m,irl,val,dupl_,info)
if (info /= 0) then
@ -400,7 +400,7 @@ subroutine psb_cins_vect_r2(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
do i=1,n
@ -569,7 +569,7 @@ subroutine psb_cinsi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)

@ -128,8 +128,8 @@ subroutine psb_cspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
call desc_a%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
if (info /= psb_success_) then
ierr(1) = info
@ -174,8 +174,8 @@ subroutine psb_cspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%indxmap%g2l(ja(1:nz),jla(1:nz),info)
call desc_a%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%g2l(ja(1:nz),jla(1:nz),info)
call a%csput(nz,ila,jla,val,ione,nrow,ione,ncol,info)
if (info /= psb_success_) then
@ -277,8 +277,8 @@ subroutine psb_cspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
goto 9999
end if
call desc_ar%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
call desc_ar%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
if (psb_errstatus_fatal()) then
ierr(1) = info

@ -259,7 +259,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_recv-1
idx = ovrlap(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -360,7 +360,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype)
end If
idx = halo(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -404,7 +404,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_send-1
idx = halo(counter+psb_elem_send_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -440,7 +440,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype)
call psb_errpush(info,name,a_err='psb_ensure_size')
goto 9999
end if
call desc_ov%indxmap%l2g(icol(1:n_elem),&
call desc_ov%l2g(icol(1:n_elem),&
& works(idxs+tot_elem+1:idxs+tot_elem+n_elem),&
& info)
@ -529,7 +529,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype)
& write(debug_unit,*) me,' ',trim(name),&
& ': going for first idx_cnv', desc_ov%indxmap%get_state()
call desc_ov%indxmap%g2l(workr(1:iszr),maskr(1:iszr),info)
call desc_ov%g2l(workr(1:iszr),maskr(1:iszr),info)
iszs = count(maskr(1:iszr)<=0)
if (iszs > size(works)) call psb_realloc(iszs,works,info)
j = 0
@ -549,7 +549,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&
& ': going for fnd_owner', desc_ov%indxmap%get_state()
call desc_a%indxmap%fnd_owner(works(1:iszs),temp,info)
call desc_a%fnd_owner(works(1:iszs),temp,info)
n_col = desc_ov%get_local_cols()
if (debug_level >= psb_debug_outer_) &
@ -559,7 +559,7 @@ Subroutine psb_dcdbldext(a,desc_a,novr,desc_ov,info, extype)
do i=1,iszs
idx = works(i)
n_col = desc_ov%get_local_cols()
call desc_ov%indxmap%g2l_ins(idx,lidx,info)
call desc_ov%g2l_ins(idx,lidx,info)
if (desc_ov%get_local_cols() > n_col ) then
!
! This is a new index. Assigning a local index as

@ -134,7 +134,7 @@ subroutine psb_dinsvi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)
case(psb_dupl_ovwrt_)
@ -280,7 +280,7 @@ subroutine psb_dins_vect(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
call x%ins(m,irl,val,dupl_,info)
if (info /= 0) then
@ -400,7 +400,7 @@ subroutine psb_dins_vect_r2(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
do i=1,n
@ -569,7 +569,7 @@ subroutine psb_dinsi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)

@ -128,8 +128,8 @@ subroutine psb_dspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
call desc_a%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
if (info /= psb_success_) then
ierr(1) = info
@ -174,8 +174,8 @@ subroutine psb_dspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%indxmap%g2l(ja(1:nz),jla(1:nz),info)
call desc_a%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%g2l(ja(1:nz),jla(1:nz),info)
call a%csput(nz,ila,jla,val,ione,nrow,ione,ncol,info)
if (info /= psb_success_) then
@ -277,8 +277,8 @@ subroutine psb_dspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
goto 9999
end if
call desc_ar%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
call desc_ar%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
if (psb_errstatus_fatal()) then
ierr(1) = info

@ -259,7 +259,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_recv-1
idx = ovrlap(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -360,7 +360,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype)
end If
idx = halo(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -404,7 +404,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_send-1
idx = halo(counter+psb_elem_send_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -440,7 +440,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype)
call psb_errpush(info,name,a_err='psb_ensure_size')
goto 9999
end if
call desc_ov%indxmap%l2g(icol(1:n_elem),&
call desc_ov%l2g(icol(1:n_elem),&
& works(idxs+tot_elem+1:idxs+tot_elem+n_elem),&
& info)
@ -529,7 +529,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype)
& write(debug_unit,*) me,' ',trim(name),&
& ': going for first idx_cnv', desc_ov%indxmap%get_state()
call desc_ov%indxmap%g2l(workr(1:iszr),maskr(1:iszr),info)
call desc_ov%g2l(workr(1:iszr),maskr(1:iszr),info)
iszs = count(maskr(1:iszr)<=0)
if (iszs > size(works)) call psb_realloc(iszs,works,info)
j = 0
@ -549,7 +549,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&
& ': going for fnd_owner', desc_ov%indxmap%get_state()
call desc_a%indxmap%fnd_owner(works(1:iszs),temp,info)
call desc_a%fnd_owner(works(1:iszs),temp,info)
n_col = desc_ov%get_local_cols()
if (debug_level >= psb_debug_outer_) &
@ -559,7 +559,7 @@ Subroutine psb_scdbldext(a,desc_a,novr,desc_ov,info, extype)
do i=1,iszs
idx = works(i)
n_col = desc_ov%get_local_cols()
call desc_ov%indxmap%g2l_ins(idx,lidx,info)
call desc_ov%g2l_ins(idx,lidx,info)
if (desc_ov%get_local_cols() > n_col ) then
!
! This is a new index. Assigning a local index as

@ -134,7 +134,7 @@ subroutine psb_sinsvi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)
case(psb_dupl_ovwrt_)
@ -280,7 +280,7 @@ subroutine psb_sins_vect(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
call x%ins(m,irl,val,dupl_,info)
if (info /= 0) then
@ -400,7 +400,7 @@ subroutine psb_sins_vect_r2(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
do i=1,n
@ -569,7 +569,7 @@ subroutine psb_sinsi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)

@ -128,8 +128,8 @@ subroutine psb_sspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
call desc_a%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
if (info /= psb_success_) then
ierr(1) = info
@ -174,8 +174,8 @@ subroutine psb_sspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%indxmap%g2l(ja(1:nz),jla(1:nz),info)
call desc_a%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%g2l(ja(1:nz),jla(1:nz),info)
call a%csput(nz,ila,jla,val,ione,nrow,ione,ncol,info)
if (info /= psb_success_) then
@ -277,8 +277,8 @@ subroutine psb_sspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
goto 9999
end if
call desc_ar%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
call desc_ar%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
if (psb_errstatus_fatal()) then
ierr(1) = info

@ -259,7 +259,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_recv-1
idx = ovrlap(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -360,7 +360,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype)
end If
idx = halo(counter+psb_elem_recv_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -404,7 +404,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype)
Do j=0,n_elem_send-1
idx = halo(counter+psb_elem_send_+j)
call desc_ov%indxmap%l2g(idx,gidx,info)
call desc_ov%l2g(idx,gidx,info)
If (gidx < 0) then
info=-3
call psb_errpush(info,name)
@ -440,7 +440,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype)
call psb_errpush(info,name,a_err='psb_ensure_size')
goto 9999
end if
call desc_ov%indxmap%l2g(icol(1:n_elem),&
call desc_ov%l2g(icol(1:n_elem),&
& works(idxs+tot_elem+1:idxs+tot_elem+n_elem),&
& info)
@ -529,7 +529,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype)
& write(debug_unit,*) me,' ',trim(name),&
& ': going for first idx_cnv', desc_ov%indxmap%get_state()
call desc_ov%indxmap%g2l(workr(1:iszr),maskr(1:iszr),info)
call desc_ov%g2l(workr(1:iszr),maskr(1:iszr),info)
iszs = count(maskr(1:iszr)<=0)
if (iszs > size(works)) call psb_realloc(iszs,works,info)
j = 0
@ -549,7 +549,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype)
if (debug_level >= psb_debug_outer_) &
& write(debug_unit,*) me,' ',trim(name),&
& ': going for fnd_owner', desc_ov%indxmap%get_state()
call desc_a%indxmap%fnd_owner(works(1:iszs),temp,info)
call desc_a%fnd_owner(works(1:iszs),temp,info)
n_col = desc_ov%get_local_cols()
if (debug_level >= psb_debug_outer_) &
@ -559,7 +559,7 @@ Subroutine psb_zcdbldext(a,desc_a,novr,desc_ov,info, extype)
do i=1,iszs
idx = works(i)
n_col = desc_ov%get_local_cols()
call desc_ov%indxmap%g2l_ins(idx,lidx,info)
call desc_ov%g2l_ins(idx,lidx,info)
if (desc_ov%get_local_cols() > n_col ) then
!
! This is a new index. Assigning a local index as

@ -134,7 +134,7 @@ subroutine psb_zinsvi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)
case(psb_dupl_ovwrt_)
@ -280,7 +280,7 @@ subroutine psb_zins_vect(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
call x%ins(m,irl,val,dupl_,info)
if (info /= 0) then
@ -400,7 +400,7 @@ subroutine psb_zins_vect_r2(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
do i=1,n
@ -569,7 +569,7 @@ subroutine psb_zinsi(m, irw, val, x, desc_a, info, dupl,local)
if (local_) then
irl(1:m) = irw(1:m)
else
call desc_a%indxmap%g2l(irw(1:m),irl(1:m),info,owned=.true.)
call desc_a%g2l(irw(1:m),irl(1:m),info,owned=.true.)
end if
select case(dupl_)

@ -128,8 +128,8 @@ subroutine psb_zspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
call desc_a%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_a%g2l_ins(ja(1:nz),jla(1:nz),info,mask=(ila(1:nz)>0))
if (info /= psb_success_) then
ierr(1) = info
@ -174,8 +174,8 @@ subroutine psb_zspins(nz,ia,ja,val,a,desc_a,info,rebuild,local)
goto 9999
end if
call desc_a%indxmap%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%indxmap%g2l(ja(1:nz),jla(1:nz),info)
call desc_a%g2l(ia(1:nz),ila(1:nz),info)
call desc_a%g2l(ja(1:nz),jla(1:nz),info)
call a%csput(nz,ila,jla,val,ione,nrow,ione,ncol,info)
if (info /= psb_success_) then
@ -277,8 +277,8 @@ subroutine psb_zspins_2desc(nz,ia,ja,val,a,desc_ar,desc_ac,info)
goto 9999
end if
call desc_ar%indxmap%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%indxmap%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
call desc_ar%g2l(ia(1:nz),ila(1:nz),info,owned=.true.)
call desc_ac%g2l_ins(ja(1:nz),jla(1:nz),info, mask=(ila(1:nz)>0))
if (psb_errstatus_fatal()) then
ierr(1) = info

@ -283,7 +283,7 @@ program cf_sample
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A : ",a)')&
& desc_a%indxmap%get_fmt()
& desc_a%get_fmt()
end if
call psb_gather(x_col_glob,x_col,desc_a,info,root=psb_root_)

@ -289,7 +289,7 @@ program df_sample
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A : ",a)')&
& desc_a%indxmap%get_fmt()
& desc_a%get_fmt()
end if
!!$ call psb_precdump(prec,info,prefix=trim(mtrx_file)//'_')

@ -286,7 +286,7 @@ program sf_sample
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A : ",a)')&
& desc_a%indxmap%get_fmt()
& desc_a%get_fmt()
end if
!!$ call psb_precdump(prec,info,prefix=trim(mtrx_file)//'_')

@ -283,7 +283,7 @@ program zf_sample
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A : ",a)')&
& desc_a%indxmap%get_fmt()
& desc_a%get_fmt()
end if
call psb_gather(x_col_glob,x_col,desc_a,info,root=psb_root_)

@ -275,7 +275,7 @@ program d_file_spmv
write(psb_out_unit,'("MBYTES/S : ",F20.3)') bdwdth
bdwdth = times*nbytes/(tt2*1.d6)
write(psb_out_unit,'("MBYTES/S (trans): ",F20.3)') bdwdth
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%indxmap%get_fmt()
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%get_fmt()
end if

@ -169,7 +169,7 @@ program pdgenspmv
write(psb_out_unit,'("MBYTES/S : ",F20.3)') bdwdth
bdwdth = times*nbytes/(tt2*1.d6)
write(psb_out_unit,'("MBYTES/S (trans): ",F20.3)') bdwdth
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%indxmap%get_fmt()
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%get_fmt()
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
end if

@ -243,7 +243,7 @@ program ppde2d
write(psb_out_unit,'("Total memory occupation for A: ",i12)')amatsize
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%indxmap%get_fmt()
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%get_fmt()
end if

@ -256,7 +256,7 @@ program ppde3d
write(psb_out_unit,'("Total memory occupation for A: ",i12)')amatsize
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%indxmap%get_fmt()
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%get_fmt()
end if

@ -242,7 +242,7 @@ program spde2d
write(psb_out_unit,'("Total memory occupation for A: ",i12)')amatsize
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%indxmap%get_fmt()
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%get_fmt()
end if

@ -256,7 +256,7 @@ program spde3d
write(psb_out_unit,'("Total memory occupation for A: ",i12)')amatsize
write(psb_out_unit,'("Total memory occupation for PREC: ",i12)')precsize
write(psb_out_unit,'("Total memory occupation for DESC_A: ",i12)')descsize
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%indxmap%get_fmt()
write(psb_out_unit,'("Storage type for DESC_A: ",a)') desc_a%get_fmt()
end if

Loading…
Cancel
Save