40 USE spmd_comm_world_mod,
ONLY : spmd_comm_world
41#include "implicit_f.inc"
54 INTEGER IAD_ELEM(2,*),FR_ELEM(*),ITAB(*)
61 INTEGER STATUS(MPI_STATUS_SIZE),
62 * REQ_SI(NSPMD),REQ_RI(NSPMD)
64,MSGTYP,J,L,NOD,PTR,NNOD,NB,ITNOD,MSGOFF
68 *
DIMENSION(:),
ALLOCATABLE :: bbufs,bbufr
71 lenrv = (iad_elem(1,nspmd+1)-iad_elem(1,1))*9
72 ALLOCATE (bbufs(lenrv),bbufr(lenrv))
79 siz = (iad_elem(1,p+1)-iad_elem(1,p))*9
83 s bbufr(l),siz,real,it_spmd(p),msgtyp,
84 g spmd_comm_world,req_ri(p),ierror)
95 DO j=iad_elem(1,p),iad_elem(1,p+1)-1
97 bbufs(l ) = mtf(1,nod)
98 bbufs(l+1) = mtf(2,nod)
99 bbufs(l+2) = mtf(3,nod)
100 bbufs(l+3) = mtf(4,nod)
101 bbufs(l+4) = mtf(5,nod)
102 bbufs(l+5) = mtf(6,nod)
103 bbufs(l+6) = mtf(7,nod)
104 bbufs(l+7) = mtf(8,nod)
105 bbufs(l+8) = mtf(9,nod)
112 IF(iad_elem(1,p+1)-iad_elem(1,p)>0)
THEN
114 siz = iads(1+p)-iads(p)
117 s bbufs(l),siz,real,it_spmd(p),msgtyp,
118 g spmd_comm_world,req_si(p),ierror)
127 nb = iad_elem(1,p+1)-iad_elem(1,p)
129 CALL mpi_wait(req_ri(p),status,ierror)
131 DO j=iad_elem(1,p),iad_elem(1,p+1)-1
133 mtf(1,nod)=mtf(1,nod)+bbufr(l)
134 mtf(2,nod)=mtf(2,nod)+bbufr(l+1)
135 mtf(3,nod)=mtf(3,nod)+bbufr(l+2)
136 mtf(4,nod)=mtf(4,nod)+bbufr(l+3)
137 mtf(5,nod)=mtf(5,nod)+bbufr(l+4)
138 mtf(6,nod)=mtf(6,nod)+bbufr(l+5)
139 mtf(7,nod)=mtf(7,nod)+bbufr(l+6)
140 mtf(8,nod)=mtf(8,nod)+bbufr(l+7)
141 mtf(9,nod)=mtf(9,nod)+bbufr(l+8)
148 siz=iads(p+1)-iads(p)
150 CALL mpi_wait(req_si(p),status,ierror)