40 1 IPARI ,INTLIST ,NBINTC ,ISLEN7 ,IRLEN7 ,
41 2 IRLEN7T ,ISLEN7T,IRLEN20 ,ISLEN20,IRLEN20T,
42 3 ISLEN20T,INTBUF_TAB,H3D_DATA )
55 USE spmd_comm_world_mod,
ONLY : spmd_comm_world
56#include
"implicit_f.inc"
71 INTEGER ,
INTENT(IN) ::
72 . NBINTC,ISLEN7, IRLEN7,IRLEN7T, ISLEN7T,
73 . IRLEN20, ISLEN20, IRLEN20T, ISLEN20T,
74 . ipari(npari,ninter), intlist(nbintc)
75 TYPE(intbuf_struct_),
INTENT(IN) :: INTBUF_TAB(NINTER)
76 TYPE(H3D_DATABASE),
INTENT(IN) :: H3D_DATA
81 INTEGER P, L, ADD, LL, NB, LEN, SIZ, KFI, LOC_PROC, MULTIMP, II,
82 . NIN, IDEB, N, MSGTYP, IERROR, NI, NOD, I,
83 . NTY, IALLOCS, IALLOCR, MSGOFF,,
84 . status(mpi_status_size),debut(ninter),
85 . adds(nspmd+1), addr(nspmd+1),
86 . req_si(nspmd),req_ri(nspmd),intcomm(nbintc)
89 my_real ,
DIMENSION(:),
ALLOCATABLE :: , BBUFR
90 LOGICAL :: IS_EFRIC_COM_NEEDED
100 is_efric_com_needed = .false.
101 intcomm(1:nbintc) = 0
105 IF(nty==7.OR.nty==24.OR.nty==25)
THEN
106 interfric = h3d_data%N_CSE_FRIC_INTER(nin)
109 is_efric_com_needed = .true.
110 ELSEIF(interfric > 0)
THEN
112 is_efric_com_needed = .true.
118 IF(is_efric_com_needed)
THEN
123 +
ALLOCATE(bbufs(iallocs+nbintc*nspmd),stat=ierror)
125 CALL ancmsg(msgid=20,anmode=aninfo)
131 +
ALLOCATE(bbufr(iallocr+nbintc*nspmd),stat=ierror)
133 CALL ancmsg(msgid=20,anmode=aninfo)
148 IF(intcomm(ii) > 0 )
THEN
158 . bbufr(add),siz,real ,it_spmd(p),msgtyp,
159 . spmd_comm_world,req_ri(p),ierror )
163 addr(nspmd+1) = addr(nspmd)+siz
177 interfric = h3d_data%N_CSE_FRIC_INTER(nin)
178 IF(intcomm(ii) > 0)
THEN
183 bbufs(l+1) = abs(
nsvfi(nin)%P(ideb+n))
185 bbufs(l+2) =
efricfi(nin)%P(ideb+n)
190 IF(h3d_data%N_SCAL_CSE_FRIC>0)
THEN
191 bbufs(l+3) =
efricgfi(nin)%P(ideb+n)
198 bbufs(ll) = (l-ll)/len
199 debut(nin) = debut(nin) + nb
207 . bbufs(add),siz,real ,it_spmd(p),msgtyp,
208 . spmd_comm_world,req_si(p),ierror )
212 adds(nspmd+1)=adds(nspmd)+siz
218 IF(addr(p+1)-addr(p)>0)
THEN
219 CALL mpi_wait(req_ri(p),status,ierror)
223 IF(
nsnsi(nin)%P(p)>0)
THEN
224 interfric = h3d_data%N_CSE_FRIC_INTER(nin)
225 IF(intcomm(ii) > 0)
THEN
229 n = nint(bbufr(l+len*(i-1)))
230 nod = intbuf_tab(nin)%NSV(n)
232 IF(interfric>0) efric(interfric,nod)= efric(interfric,nod)+ bbufr(l+len*(i-1)+1)
233 IF(h3d_data%N_SCAL_CSE_FRIC>0) efricg(nod)= efricg(nod)+ bbufr(l+len*(i-1)+2)
250 IF(adds(p+1)-adds(p)>0)
THEN
251 CALL mpi_wait(req_si(p),status,ierror)
subroutine spmd_exch_efric(ipari, intlist, nbintc, islen7, irlen7, irlen7t, islen7t, irlen20, islen20, irlen20t, islen20t, intbuf_tab, h3d_data)
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)