New adjcncy and a2a fnd_owner

Reimplement adjcncy_fnd_owner to use alltoallv. Version with
sends/irecv still available under compile time constant.

Reimplement a2a_fnd_owner to use adjcncy_fnd_owner. Older version
still available under compile time constant.
fnd_owner
Salvatore Filippone 5 years ago
parent cf3fce32c3
commit caec98e942

@ -67,7 +67,7 @@ subroutine psi_a2a_fnd_owner(idx,iprc,idxmap,info)
integer(psb_lpk_), allocatable :: answers(:,:), idxsrch(:,:), hproc(:)
integer(psb_ipk_), allocatable :: helem(:), hhidx(:)
integer(psb_ipk_), allocatable :: helem(:), hhidx(:), tmpadj(:)
integer(psb_mpk_), allocatable :: hsz(:),hidx(:), &
& sdsz(:),sdidx(:), rvsz(:), rvidx(:)
integer(psb_mpk_) :: icomm, minfo, iictxt
@ -75,7 +75,7 @@ subroutine psi_a2a_fnd_owner(idx,iprc,idxmap,info)
& last_ih, last_j, nv
integer(psb_lpk_) :: mglob, ih
integer(psb_ipk_) :: ictxt,np,me, nresp
logical, parameter :: gettime=.false.
logical, parameter :: gettime=.false., use_adj=.true.
real(psb_dpk_) :: t0, t1, t2, t3, t4, tamx, tidx
character(len=20) :: name
@ -103,10 +103,22 @@ subroutine psi_a2a_fnd_owner(idx,iprc,idxmap,info)
goto 9999
end if
if (use_adj) then
!
! Reuse the other version by tricking it with an adjcncy list
! that contains everybody but ME.
!
nv = size(idx)
call psb_realloc(np-1,tmpadj,info)
tmpadj(1:me) = [(i,i=0,me-1)]
tmpadj(me+1:np-1) = [(i,i=me+1,np-1)]
call psi_adjcncy_fnd_owner(idx,iprc,tmpadj,idxmap,info)
else
if (gettime) then
t0 = psb_wtime()
end if
nv = size(idx)
call psb_realloc(nv,iprc,info)
if (info /= psb_success_) then
@ -275,6 +287,7 @@ subroutine psi_a2a_fnd_owner(idx,iprc,idxmap,info)
end do
end if
end do
if (gettime) then
call psb_barrier(ictxt)
t1 = psb_wtime()
@ -288,6 +301,7 @@ subroutine psi_a2a_fnd_owner(idx,iprc,idxmap,info)
write(psb_out_unit,'(" a2a_owner remainedr : ",es10.4)') t1
endif
end if
end if
call psb_erractionrestore(err_act)
return

@ -61,7 +61,7 @@ subroutine psi_adjcncy_fnd_owner(idx,iprc,adj,idxmap,info)
integer(psb_lpk_), allocatable :: rmtidx(:)
integer(psb_ipk_), allocatable :: tproc(:), lclidx(:)
integer(psb_mpk_), allocatable :: hsz(:),hidx(:), &
integer(psb_mpk_), allocatable :: hsz(:),hidx(:), sdidx(:), rvidx(:),&
& sdsz(:), rvsz(:), sdhd(:), rvhd(:), p2pstat(:,:)
integer(psb_mpk_) :: prc, p2ptag, iret
integer(psb_mpk_) :: icomm, minfo, iictxt
@ -69,7 +69,7 @@ subroutine psi_adjcncy_fnd_owner(idx,iprc,adj,idxmap,info)
& last_ih, last_j, nidx, nrecv, nadj
integer(psb_lpk_) :: mglob, ih
integer(psb_ipk_) :: ictxt,np,me
logical, parameter :: gettime=.false., new_impl=.true.
logical, parameter :: gettime=.false., new_impl=.true., a2av_impl=.true., debug=.false.
real(psb_dpk_) :: t0, t1, t2, t3, t4, tamx, tidx
character(len=20) :: name
@ -111,6 +111,76 @@ subroutine psi_adjcncy_fnd_owner(idx,iprc,adj,idxmap,info)
iprc = -1
! write(0,*) me,name,' Going through ',nidx,nadj
if (a2av_impl) then
!
! First simple minded version with auxiliary arrays
! dimensioned on NP.
! Do the exchange with an alltoallv
!
!
Allocate(hidx(0:np),hsz(np),sdsz(0:np-1),rvsz(0:np-1), &
& sdidx(0:np),rvidx(0:np),stat=info)
!
! Same send buffer for everybody
!
sdidx(:) = 0
!
! First, send sizes according to adjcncy list
!
sdsz = 0
do j=1, nadj
sdsz(adj(j)) = nidx
end do
!write(0,*)me,' Check on sizes into a2a:',adj(:),nadj,':',sdsz(:)
call mpi_alltoall(sdsz,1,psb_mpi_mpk_,&
& rvsz,1,psb_mpi_mpk_,icomm,minfo)
rvidx(0) = 0
do i=0, np-1
rvidx(i+1) = rvidx(i) + rvsz(i)
end do
hsize = rvidx(np)
! write(0,*)me,' Check on sizes from a2a:',hsize,rvsz(:)
!
! Second, allocate buffers and exchange data
!
Allocate(rmtidx(hsize),lclidx(max(hsize,nidx*nadj)),tproc(max(hsize,nidx)),stat=info)
if (info /= psb_success_) then
call psb_errpush(psb_err_from_subroutine_,name,a_err='Allocate')
goto 9999
end if
call mpi_alltoallv(idx,sdsz,sdidx,psb_mpi_lpk_,&
& rmtidx,rvsz,rvidx,psb_mpi_lpk_,icomm,iret)
!
! Third, compute local answers
!
call idxmap%g2l(rmtidx(1:hsize),lclidx(1:hsize),info,owned=.true.)
do i=1, hsize
tproc(i) = -1
if ((0 < lclidx(i)).and. (lclidx(i) <= n_row)) tproc(i) = me
end do
!
! Fourth, exchange the answers
!
! Adjust sdidx for receive in lclidx array (reused)
do i=0,np-1
sdidx(i+1) = sdidx(i) + sdsz(i)
end do
call mpi_alltoallv(tproc,rvsz,rvidx,psb_mpi_ipk_,&
& lclidx,sdsz,sdidx,psb_mpi_ipk_,icomm,iret)
do i=0, np-1
if (sdsz(i)>0) then
iprc(1:nidx) = max(iprc(1:nidx), lclidx(sdidx(i)+1:sdidx(i)+sdsz(i)))
end if
end do
if (debug) write(0,*) me,' End of adjcncy_fnd ',iprc(1:nidx)
else
if (new_impl) then
!
! First simple minded version with auxiliary arrays
@ -228,8 +298,10 @@ subroutine psi_adjcncy_fnd_owner(idx,iprc,adj,idxmap,info)
!if (nidx > 0) call psb_rcv(ictxt,tproc(1:nidx),adj(j))
iprc(1:nidx) = max(iprc(1:nidx), lclidx((j-1)*nidx+1:(j-1)*nidx+nidx))
end do
if (debug) write(0,*) me,' End of adjcncy_fnd ',iprc(1:nidx)
else
Allocate(hidx(0:np),hsz(np),&
& sdsz(0:np-1),rvsz(0:np-1),stat=info)
!
@ -297,6 +369,8 @@ subroutine psi_adjcncy_fnd_owner(idx,iprc,adj,idxmap,info)
iprc(1:nidx) = max(iprc(1:nidx), tproc(1:nidx))
end do
end if
end if
call psb_erractionrestore(err_act)
return

Loading…
Cancel
Save