OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_sync_mmxg.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/.
23C
24!||====================================================================
25!|| spmd_sync_mmxg ../engine/source/mpi/interfaces/spmd_sync_mmxg.F
26!||--- calls -----------------------------------------------------
27!||====================================================================
28 SUBROUTINE spmd_sync_mmxg(
29 1 ISENDTO,IRCVFROM,NEWFRONT,XSLV_L,XMSR_L,
30 2 VSLV_L ,VMSR_L ,INTLIST ,NINTC ,TZINF ,
31 3 SIZE_T ,IPARI , DELTA_PMAX_GAP,MAXDGAP )
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35#include "implicit_f.inc"
36C-----------------------------------------------------------------
37C M e s s a g e P a s s i n g
38C-----------------------------------------------
39#include "spmd.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com04_c.inc"
44#include "param_c.inc"
45#include "task_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER ISENDTO(NINTER+1,*) ,IRCVFROM(NINTER+1,*),
50 . NEWFRONT(*), NINTC, INTLIST(*), IPARI(NPARI,*)
51 my_real
52 . xslv_l(18,*), xmsr_l(12,*), vslv_l(6,*),
53 . vmsr_l(6,*), tzinf(*), size_t(*),delta_pmax_gap(*),
54 . maxdgap(ninter)
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58#ifdef MPI
59 INTEGER LOC_PROC,IERROR,I_LEN,myop,
60 . KK, L, J, NIN, REQ,
61 . STATUS(MPI_STATUS_SIZE),type_reduc
62 parameter(i_len = 46)
63 my_real
64 . sbuf(nintc*i_len), rbuf(nintc*i_len)
65 INTEGER REDUCE_MMX
66 EXTERNAL reduce_mmx
67C-----------------------------------------------
68C S o u r c e L i n e s
69C-----------------------------------------------
70C
71 loc_proc = ispmd+1
72 IF(ircvfrom(ninter+1,loc_proc)>0.OR.
73 + isendto(ninter+1,loc_proc)>0) THEN
74
75! need to define I_LEN contiguous blocks to avoid that intel mpi splits
76! the buffers
77 call mpi_type_contiguous(i_len,real,type_reduc,ierror)
78! need to validate the Type_contiguous
79 call mpi_type_commit(type_reduc,ierror)
80
81 call mpi_op_create(reduce_mmx, .true., myop, ierror)
82
83C Pack original data
84 l = 0
85 DO kk=1,nintc
86 nin = intlist(kk)
87C X MIN/MAX
88 DO j=1,18
89 sbuf(l+j) = xslv_l(j,nin)
90 END DO
91 l = l + 18
92C
93 DO j=1,12
94 sbuf(l+j) = xmsr_l(j,nin)
95 END DO
96 l = l + 12
97C V MIN/MAX
98 DO j=1,6
99 sbuf(l+j) = vslv_l(j,nin)
100 END DO
101 l = l + 6
102C
103 DO j=1,6
104 sbuf(l+j) = vmsr_l(j,nin)
105 END DO
106 l = l + 6
107 IF(ipari(7,nin)/=17)THEN
108C NEWFRONT
109 sbuf(l+1) = newfront(nin)
110 ELSE ! interface 17 avec courbure
111C SIZE
112 sbuf(l+1) = size_t(nin)
113 END IF
114 l = l + 1
115C TZINF
116 sbuf(l+1) = tzinf(kk)
117 l = l + 1
118C DELTA_PMAX_GAP
119 sbuf(l+1) = delta_pmax_gap(nin)
120 l = l + 1
121C T25 main gap changes with thickness change
122 sbuf(l+1) = maxdgap(nin)
123 l = l + 1
124 END DO
125C
126! -+-+-+-+-+-+-+-+-+-
127! OLD FORMULATION : bug with intel MPI
128! call MPI_AllReduce(SBUF, RBUF, NINTC*I_LEN, real, myop,
129! & COMM_CONT, ierror)
130! -+-+-+-+-+-+-+-+-+-
131
132! NEW FORMULATION
133 call mpi_allreduce(sbuf, rbuf, nintc, type_reduc, myop,
134 & comm_cont, ierror)
135
136
137cc call MPI_IAllReduce(SBUF, RBUF, NINTC*I_LEN, real, myop,
138cc & COMM_CONT, REQ, IERROR)
139cc call MPI_WAIT(req,status,ierror)
140C Unpack results
141
142 l = 0
143 DO kk=1,nintc
144 nin = intlist(kk)
145 IF(ircvfrom(nin,loc_proc)/=0.OR.
146 + isendto(nin,loc_proc)/=0)THEN
147 DO j=1,18
148 xslv_l(j,nin) = rbuf(l+j)
149 END DO
150 l = l + 18
151 DO j=1,12
152 xmsr_l(j,nin) = rbuf(l+j)
153 END DO
154 l = l + 12
155 DO j=1,6
156 vslv_l(j,nin) = rbuf(l+j)
157 END DO
158 l = l + 6
159 DO j=1,6
160 vmsr_l(j,nin) = rbuf(l+j)
161 END DO
162 l = l + 6
163 IF(ipari(7,nin)/=17)THEN
164 newfront(nin) = nint(rbuf(l+1))
165 ELSE ! interface 17 avec courbure
166 size_t(nin) = rbuf(l+1)
167 END IF
168 l = l + 1
169 tzinf(kk) = rbuf(l+1)
170 l = l + 1
171 delta_pmax_gap(nin) = rbuf(l+1)
172 l = l + 1
173C T25 main gap changes with thickness change
174 maxdgap(nin) = rbuf(l+1)
175 l = l + 1
176 ELSE
177 l = l + 46
178 END IF
179 END DO
180
181C
182 call mpi_type_free(type_reduc,ierror)
183 call mpi_op_free(myop, ierror)
184 END IF
185
186
187#endif
188 RETURN
189 END
subroutine mpi_type_free(newtyp, ierr_mpi)
Definition mpi.f:399
subroutine mpi_type_contiguous(length, datatype, newtype, ierr_mpi)
Definition mpi.f:406
subroutine mpi_allreduce(sendbuf, recvbuf, cnt, datatype, operation, comm, ierr)
Definition mpi.f:103
subroutine mpi_type_commit(newtyp, ierr_mpi)
Definition mpi.f:393
subroutine mpi_op_create(func, commute, op, ierr)
Definition mpi.f:412
subroutine mpi_op_free(op, ierr)
Definition mpi.f:421
subroutine spmd_sync_mmxg(isendto, ircvfrom, newfront, xslv_l, xmsr_l, vslv_l, vmsr_l, intlist, nintc, tzinf, size_t, ipari, delta_pmax_gap, maxdgap)