OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_i18kine_com_v.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| spmd_i18kine_com_v ../engine/source/mpi/interfaces/spmd_i18kine_com_v.F
25!||--- called by ------------------------------------------------------
26!|| i18main_kine_2 ../engine/source/interfaces/int18/i18main_kine.F
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../engine/source/output/message/message.F
29!|| arret ../engine/source/system/arret.F
30!||--- uses -----------------------------------------------------
31!|| intbufdef_mod ../common_source/modules/interfaces/intbufdef_mod.F90
32!|| message_mod ../engine/share/message_module/message_mod.F
33!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
34!|| tri7box ../engine/share/modules/tri7box.F
35!||====================================================================
36 SUBROUTINE spmd_i18kine_com_v(IPARI,INTBUF_TAB,
37 * MTF,A,ITAB)
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 . mtf(14,*),a(3,*)
67
68 TYPE(intbuf_struct_) INTBUF_TAB(*)
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72#ifdef MPI
73 INTEGER STATUS(MPI_STATUS_SIZE),
74 * req_si(nspmd),req_ri(nspmd)
75 INTEGER P,LENSD,LENRV,IADS(NSPMD+1),IADR(NSPMD+1),IERROR,
76 * siz,loc_proc,msgtyp,msgoff,ideb(ninter)
77 INTEGER NIN,NTY,INACTI
78 INTEGER J,L,NB,NN,K,N,NOD,MODE,LEN,ALEN,ND
79 my_real ,
80 * DIMENSION(:), ALLOCATABLE :: bbufs, bbufr
81 DATA msgoff/153/
82C-----------------------------------------------
83C Sur la type 18KINE, il faut communiquer les accelerations des nds seconds
84
85
86 loc_proc = ispmd+1
87 iads = 0
88 iadr = 0
89 lensd = 0
90 lenrv = 0
91
92 alen=3
93C Comptage des tailles de buffer Receeption et envoi
94 DO p=1,nspmd
95 iadr(p)=lenrv+1
96 DO nin=1,ninter
97 nty=ipari(7,nin)
98 inacti =ipari(22,nin)
99 IF((nty==7.and.ipari(34,nin)==-2.and.inacti==7).OR.
100 . (nty==22.and.ipari(34,nin)==-2.and.inacti==7))THEN
101 lensd = lensd + nsnsi(nin)%P(p)*alen
102 lenrv = lenrv + nsnfi(nin)%P(p)*alen
103 ENDIF
104 ENDDO
105 ENDDO
106 iadr(nspmd+1)=lenrv+1
107 IF(lensd>0)THEN
108 ALLOCATE(bbufs(lensd),stat=ierror)
109 IF(ierror/=0) THEN
110 CALL ancmsg(msgid=20,anmode=aninfo)
111 CALL arret(2)
112 ENDIF
113 ENDIF
114
115C Preparation du recieve
116 IF(lenrv>0)THEN
117 ALLOCATE(bbufr(lenrv),stat=ierror)
118 IF(ierror/=0) THEN
119 CALL ancmsg(msgid=20,anmode=aninfo)
120 CALL arret(2)
121 ENDIF
122 ENDIF
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
133 IF((nty==7.and.ipari(34,nin)==-2.and.inacti==7).OR.
134 . (nty==22.and.ipari(34,nin)==-2.and.inacti==7))THEN
135 nb = nsnsi(nin)%P(p)
136C Preparation du send
137 DO nn=1,nb
138 nd = nsvsi(nin)%P(ideb(nin)+nn)
139 nod=intbuf_tab(nin)%NSV(nd)
140 bbufs(l )=mtf(1,nod)
141 bbufs(l+1)=mtf(2,nod)
142 bbufs(l+2)=mtf(3,nod)
143C MTFI(4-6 ne sont pas des valeurs de cumuls,
144c ils sont initialises dans les parties ou on en a besoin
145c il est inutile de les communiquer
146c BBUFS(L+3)=MTF(4,NOD)
147c BBUFS(L+4)=MTF(5,NOD)
148c BBUFS(L+5)=MTF(6,NOD)
149 l=l+3
150 ENDDO
151 ideb(nin)=ideb(nin)+nb
152 ENDIF
153 ENDDO
154
155 siz = l-iads(p)
156 IF(siz>0)THEN
157 msgtyp = msgoff
158C Send
159 CALL mpi_isend(
160 . bbufs(iads(p)),siz,real ,it_spmd(p),msgtyp,
161 . spmd_comm_world,req_si(p),ierror )
162 ENDIF
163 ENDIF
164 ENDDO
165 iads(nspmd+1)=l
166C Recieve
167 l=0
168 ideb = 0
169 DO p=1, nspmd
170 l=0
171 siz=iadr(p+1)-iadr(p)
172 IF (siz > 0) THEN
173 msgtyp = msgoff
174 CALL mpi_recv( bbufr(iadr(p)),siz,real,it_spmd(p),msgtyp,
175 * spmd_comm_world,status,ierror )
176 DO nin=1,ninter
177 nty =ipari(7,nin)
178 inacti =ipari(22,nin)
179
180 nb = nsnfi(nin)%P(p)
181
182 IF((nty==7.and.ipari(34,nin)==-2.and.inacti==7).OR.
183 . (nty==22.and.ipari(34,nin)==-2.and.inacti==7))THEN
184
185 IF (nb > 0)THEN
186 DO k=1,nb
187 mtfi_v(nin)%P(1,ideb(nin)+k)=bbufr(iadr(p)+l)
188 mtfi_v(nin)%P(2,ideb(nin)+k)=bbufr(iadr(p)+l+1)
189 mtfi_v(nin)%P(3,ideb(nin)+k)=bbufr(iadr(p)+l+2)
190c MTFI_V(NIN)%P(4,IDEB(NIN)+K)=BBUFR(IADR(P)+L+3)
191c MTFI_V(NIN)%P(5,IDEB(NIN)+K)=BBUFR(IADR(P)+L+4)
192c MTFI_V(NIN)%P(6,IDEB(NIN)+K)=BBUFR(IADR(P)+L+5)
193 l=l+3
194 ENDDO
195 ENDIF
196 ENDIF
197 ideb(nin)=ideb(nin)+nb
198 ENDDO
199 ENDIF
200 ENDDO
201C Fin du send
202 DO p = 1, nspmd
203 siz=iads(p+1)-iads(p)
204 IF(siz>0) THEN
205 CALL mpi_wait(req_si(p),status,ierror)
206 ENDIF
207 ENDDO
208
209 IF (ALLOCATED(bbufs)) DEALLOCATE(bbufs)
210 IF (ALLOCATED(bbufr)) DEALLOCATE(bbufr)
211#endif
212 RETURN
213 END
#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(int_pointer), dimension(:), allocatable nsvsi
Definition tri7box.F:485
type(int_pointer), dimension(:), allocatable nsnsi
Definition tri7box.F:491
type(real_pointer2), dimension(:), allocatable mtfi_v
Definition tri7box.F:459
type(int_pointer), dimension(:), allocatable nsnfi
Definition tri7box.F:440
subroutine spmd_i18kine_com_v(ipari, intbuf_tab, mtf, a, itab)
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