OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_i18kine_com_a.F File Reference
#include "implicit_f.inc"
#include "spmd.inc"
#include "param_c.inc"
#include "com04_c.inc"
#include "task_c.inc"
#include "com01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine spmd_i18kine_com_a (ipari, intbuf_tab, a, itab)

Function/Subroutine Documentation

◆ spmd_i18kine_com_a()

subroutine spmd_i18kine_com_a ( integer, dimension(npari,*) ipari,
type(intbuf_struct_), dimension(*) intbuf_tab,
a,
integer, dimension(*) itab )

Definition at line 36 of file spmd_i18kine_com_a.F.

38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE tri7box
42 USE message_mod
43 USE intbufdef_mod
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47 USE spmd_comm_world_mod, ONLY : spmd_comm_world
48#include "implicit_f.inc"
49C-----------------------------------------------
50C M e s s a g e P a s s i n g
51C-----------------------------------------------
52#include "spmd.inc"
53C-----------------------------------------------
54C C o m m o n B l o c k s
55C-----------------------------------------------
56#include "param_c.inc"
57#include "com04_c.inc"
58#include "task_c.inc"
59#include "com01_c.inc"
60C-----------------------------------------------
61C D u m m y A r g u m e n t s
62C-----------------------------------------------
63 INTEGER IPARI(NPARI,*),ITAB(*)
64C
66 . a(3,*)
67 TYPE(INTBUF_STRUCT_) INTBUF_TAB(*)
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71#ifdef MPI
72 INTEGER STATUS(MPI_STATUS_SIZE),
73 * REQ_SI(NSPMD),REQ_RI(NSPMD)
74 INTEGER P,LENSD,LENRV,IADS(NSPMD+1),IADR(NSPMD+1),IERROR,
75 * SIZ,LOC_PROC,MSGTYP,MSGOFF,IDEB(NINTER)
76 INTEGER NIN,NTY,INACTI
77 INTEGER J,L,NB,NN,K,N,NOD,MODE,LEN,ALEN,ND
78 my_real ,
79 * DIMENSION(:), ALLOCATABLE :: bbufs, bbufr
80 DATA msgoff/152/
81C-----------------------------------------------
82C Sur la type 18KINE, il faut communiquer les accelerations des nds seconds
83
84 loc_proc = ispmd+1
85 iads = 0
86 iadr = 0
87 lensd = 0
88 lenrv = 0
89
90 alen=3
91C Comptage des tailles de buffer Receeption et envoi
92 DO p=1,nspmd
93 iadr(p)=lenrv+1
94 DO nin=1,ninter
95 nty=ipari(7,nin)
96 inacti =ipari(22,nin)
97 IF((nty==7.and.ipari(34,nin)==-2.and.inacti==7).OR.
98 . (nty==22.and.ipari(34,nin)==-2.and.inacti==7))THEN
99 lensd = lensd + nsnsi(nin)%P(p)*alen
100 lenrv = lenrv + nsnfi(nin)%P(p)*alen
101 ENDIF
102 ENDDO
103 ENDDO
104 iadr(nspmd+1)=lenrv+1
105
106 IF(lensd>0)THEN
107 ALLOCATE(bbufs(lensd),stat=ierror)
108 IF(ierror/=0) THEN
109 CALL ancmsg(msgid=20,anmode=aninfo)
110 CALL arret(2)
111 ENDIF
112 ENDIF
113
114C Preparation du recieve
115 IF(lenrv>0)THEN
116 ALLOCATE(bbufr(lenrv),stat=ierror)
117 IF(ierror/=0) THEN
118 CALL ancmsg(msgid=20,anmode=aninfo)
119 CALL arret(2)
120 ENDIF
121 ENDIF
122
123C Send
124 l=1
125 ideb = 0
126 DO p=1, nspmd
127 iads(p)=l
128 IF (p/= loc_proc) THEN
129 DO nin=1,ninter
130 nty =ipari(7,nin)
131 inacti =ipari(22,nin)
132 IF((nty==7.and.ipari(34,nin)==-2.and.inacti==7).OR.
133 . (nty==22.and.ipari(34,nin)==-2.and.inacti==7))THEN
134 nb = nsnsi(nin)%P(p)
135C Preparation du send
136 DO nn=1,nb
137 nd = nsvsi(nin)%P(ideb(nin)+nn)
138 nod=intbuf_tab(nin)%NSV(nd)
139 bbufs(l )=a(1,nod)
140 bbufs(l+1)=a(2,nod)
141 bbufs(l+2)=a(3,nod)
142 l=l+3
143 ENDDO
144 ENDIF
145 ideb(nin)=ideb(nin)+nb
146 ENDDO
147
148 siz = l-iads(p)
149 IF(siz>0)THEN
150 msgtyp = msgoff
151C Send
152 CALL mpi_isend(
153 . bbufs(iads(p)),siz,real ,it_spmd(p),msgtyp,
154 . spmd_comm_world,req_si(p),ierror )
155 ENDIF
156 ENDIF
157 ENDDO
158 iads(nspmd+1)=l
159C Recieve
160 l=0
161 ideb = 0
162
163 DO p=1, nspmd
164 l=0
165 siz=iadr(p+1)-iadr(p)
166 IF (siz > 0) THEN
167 msgtyp = msgoff
168 CALL mpi_recv( bbufr(iadr(p)),siz,real,it_spmd(p),msgtyp,
169 * spmd_comm_world,status,ierror )
170 DO nin=1,ninter
171 nty =ipari(7,nin)
172 inacti =ipari(22,nin)
173
174 nb = nsnfi(nin)%P(p)
175
176 IF((nty==7.and.ipari(34,nin)==-2.and.inacti==7).OR.
177 . (nty==22.and.ipari(34,nin)==-2.and.inacti==7))THEN
178
179 IF (nb > 0)THEN
180 DO k=1,nb
181 i18kafi(nin)%P(1,ideb(nin)+k)=bbufr(iadr(p)+l)
182 i18kafi(nin)%P(2,ideb(nin)+k)=bbufr(iadr(p)+l+1)
183 i18kafi(nin)%P(3,ideb(nin)+k)=bbufr(iadr(p)+l+2)
184 l=l+3
185 ENDDO
186 ENDIF
187 ENDIF
188 ideb(nin)=ideb(nin)+nb
189 ENDDO
190 ENDIF
191 ENDDO
192
193C Fin du send
194 DO p = 1, nspmd
195 IF (p==nspmd)THEN
196 siz=lensd-iads(p)
197 ELSE
198 siz=iads(p+1)-iads(p)
199 ENDIF
200 IF(siz>0) THEN
201 CALL mpi_wait(req_si(p),status,ierror)
202 ENDIF
203 ENDDO
204
205 IF (ALLOCATED(bbufs)) DEALLOCATE(bbufs)
206 IF (ALLOCATED(bbufr)) DEALLOCATE(bbufr)
207
208#endif
209 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine mpi_recv(buf, cnt, datatype, source, tag, comm, status, ierr)
Definition mpi.f:461
subroutine mpi_isend(buf, cnt, datatype, dest, tag, comm, ireq, ierr)
Definition mpi.f:382
subroutine mpi_wait(ireq, status, ierr)
Definition mpi.f:525
type(real_pointer2), dimension(:), allocatable i18kafi
Definition tri7box.F:459
type(int_pointer), dimension(:), allocatable nsvsi
Definition tri7box.F:485
type(int_pointer), dimension(:), allocatable nsnsi
Definition tri7box.F:491
type(int_pointer), dimension(:), allocatable nsnfi
Definition tri7box.F:440
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)
Definition message.F:889
subroutine arret(nn)
Definition arret.F:87