OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_i18kine_com_ms.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_ms (ipari, intbuf_tab, mtf, ms, itab)

Function/Subroutine Documentation

◆ spmd_i18kine_com_ms()

subroutine spmd_i18kine_com_ms ( integer, dimension(npari,*) ipari,
type(intbuf_struct_), dimension(*) intbuf_tab,
mtf,
ms,
integer, dimension(*) itab )

Definition at line 36 of file spmd_i18kine_com_ms.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 . mtf(14,*),ms(*)
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/151/
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=1
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 )=ms(nod)
140 l=l+1
141 ENDDO
142 ENDIF
143 ideb(nin)=ideb(nin)+nb
144 ENDDO
145
146 siz = l-iads(p)
147 IF(siz>0)THEN
148 msgtyp = msgoff
149C Send
150 CALL mpi_isend(
151 . bbufs(iads(p)),siz,real ,it_spmd(p),msgtyp,
152 . spmd_comm_world,req_si(p),ierror )
153 ENDIF
154 ENDIF
155 ENDDO
156 iads(nspmd+1)=l
157C Recieve
158 l=0
159 ideb = 0
160
161 DO p=1, nspmd
162 l=0
163 siz=iadr(p+1)-iadr(p)
164 IF (siz > 0) THEN
165 msgtyp = msgoff
166 CALL mpi_recv( bbufr(iadr(p)),siz,real,it_spmd(p),msgtyp,
167 * spmd_comm_world,status,ierror )
168 DO nin=1,ninter
169 nty =ipari(7,nin)
170 inacti =ipari(22,nin)
171
172 nb = nsnfi(nin)%P(p)
173
174 IF((nty==7.and.ipari(34,nin)==-2.and.inacti==7).OR.
175 . (nty==22.and.ipari(34,nin)==-2.and.inacti==7))THEN
176
177 IF (nb > 0)THEN
178 DO k=1,nb
179 msfi(nin)%P(ideb(nin)+k)=bbufr(iadr(p)+l)
180 l=l+1
181 ENDDO
182 ENDIF
183 ENDIF
184 ideb(nin)=ideb(nin)+nb
185 ENDDO
186 ENDIF
187 ENDDO
188
189C Fin du send
190 DO p = 1, nspmd
191 IF (p==nspmd)THEN
192 siz=lensd-iads(p)
193 ELSE
194 siz=iads(p+1)-iads(p)
195 ENDIF
196 IF(siz>0) THEN
197 CALL mpi_wait(req_si(p),status,ierror)
198 ENDIF
199 ENDDO
200
201 IF (ALLOCATED(bbufs)) DEALLOCATE(bbufs)
202 IF (ALLOCATED(bbufr)) DEALLOCATE(bbufr)
203#endif
204 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(int_pointer), dimension(:), allocatable nsvsi
Definition tri7box.F:485
type(int_pointer), dimension(:), allocatable nsnsi
Definition tri7box.F:491
type(real_pointer), dimension(:), allocatable msfi
Definition tri7box.F:449
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