OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
arezon.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!|| arezon_mod ../engine/source/ale/arezon.F
25!||--- called by ------------------------------------------------------
26!|| alethe ../engine/source/ale/alethe.F
27!||====================================================================
29 CONTAINS
30!||====================================================================
31!|| arezon ../engine/source/ale/arezon.F
32!||--- called by ------------------------------------------------------
33!|| alethe ../engine/source/ale/alethe.F
34!||--- calls -----------------------------------------------------
35!|| arezo2 ../engine/source/ale/ale2d/arezo2.F
36!|| arezo3 ../engine/source/ale/ale3d/arezo3.F
37!|| brezo2 ../engine/source/ale/ale2d/brezo2.F
38!|| initbuf ../engine/share/resol/initbuf.F
39!|| my_barrier ../engine/source/system/machine.F
40!|| spmd_e1vois ../engine/source/mpi/fluid/spmd_cfd.F
41!||--- uses -----------------------------------------------------
42!|| ale_connectivity_mod ../common_source/modules/ale/ale_connectivity_mod.F
43!|| arezo2_mod ../engine/source/ale/ale2d/arezo2.F
44!|| arezo3_mod ../engine/source/ale/ale3d/arezo3.F
45!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
46!|| initbuf_mod ../engine/share/resol/initbuf.F
47!|| multimat_param_mod ../common_source/modules/multimat_param_mod.F90
48!||====================================================================
49 SUBROUTINE arezon(
50 1 IPARG ,ELBUF_STR,FLUX ,PHI ,ALE_CONNECT ,
51 2 NVAR ,NV ,ITASK ,NERCVOIS,
52 3 NESDVOIS,LERCVOIS ,LESDVOIS,LENCOM,BHOLE ,
53 4 ITRIMAT ,OPT_FLAG_MAT_EOS)
54C-----------------------------------------------
55C M o d u l e s
56C-----------------------------------------------
57 USE initbuf_mod
58 USE elbufdef_mod
60 USE multimat_param_mod , ONLY : m51_n0phas, m51_nvphas
61 USE arezo3_mod , ONLY : arezo3
62 USE arezo2_mod , ONLY : arezo2
63C-----------------------------------------------
64C I m p l i c i t T y p e s
65C-----------------------------------------------
66#include "implicit_f.inc"
67C-----------------------------------------------
68C C o m m o n B l o c k s
69C-----------------------------------------------
70#include "com01_c.inc"
71#include "com04_c.inc"
72#include "vect01_c.inc"
73#include "param_c.inc"
74#include "task_c.inc"
75C-----------------------------------------------
76C D u m m y A r g u m e n t s
77C-----------------------------------------------
78 my_real flux(*), phi(*)
79 INTEGER NVAR, ITASK, LENCOM,ITRIMAT,NV,
80 . IPARG(NPARG,NGROUP),
81 . NERCVOIS(*),NESDVOIS(*),LERCVOIS(*),LESDVOIS(*),
82 . bhole(*)
83 TYPE (ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET :: ELBUF_STR
84 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECT
85 INTEGER,INTENT(IN),OPTIONAL :: OPT_FLAG_MAT_EOS
86C-----------------------------------------------
87C L o c a l V a r i a b l e s
88C-----------------------------------------------
89 INTEGER :: NG, IRS, IRE, I, J, K, NM, NMN, NFX, ADD, ADD0,IDX,INDX,NEL
90 INTEGER :: NUVAR_MAT !< number of user variable (MATERIAL) to rezon
91 INTEGER :: NUVAR_EOS !< number of user variable (EOS) to rezon
92 my_real, DIMENSION(:), POINTER :: VAR,SIG,VOL, TAG22,TEMP
93 INTEGER :: FLAG_MAT_EOS
94C-----------------------------------------------
95C S o u r c e L i n e s
96C-----------------------------------------------
97 flag_mat_eos = 0
98 IF(PRESENT(opt_flag_mat_eos))flag_mat_eos = opt_flag_mat_eos
99 idx=nv
100 nmn=max(1,nmult)
101 DO nm=1,nmn
102C---------------------
103 CALL my_barrier
104C---------------------
105 DO ng=itask+1,ngroup,nthread
106C ALE ON / OFF
107 IF (iparg(76, ng) == 1) cycle ! --> OFF
108 CALL initbuf(iparg ,ng ,
109 2 mtn ,llt ,nft ,iad ,ity ,
110 3 npt ,jale ,ismstr ,jeul ,jtur ,
111 4 jthe ,jlag ,jmult ,jhbe ,jivf ,
112 5 nvaux ,jpor ,jcvt ,jclose ,jplasol ,
113 6 irep ,iint ,igtyp ,israt ,isrot ,
114 7 icsen ,isorth ,isorthg ,ifailure,jsms )
115 !-----------------------------!
116 ! PRECONDITIONS !
117 !-----------------------------!
118 nuvar_mat = iparg(81,ng)
119 nuvar_eos = iparg(82,ng)
120 IF (nvar == 11)THEN
121 IF (flag_mat_eos == 0 .OR. idx == 0) cycle ! %VAR (MAT and EOS)
122 IF(flag_mat_eos == 1)THEN
123 IF(idx > nuvar_mat) cycle ! rezon uvar( I, 1:NUVAR_MAT) only
124 ELSEIF (flag_mat_eos == 2)THEN
125 IF(idx > nuvar_eos) cycle ! rezon uvar( I, 1:NUVAR_MAT) only
126 ENDIF
127 ENDIF
128 IF (itrimat > 0 .AND. mtn /= 51) cycle
129 IF (jale+jeul == 0) cycle
130 IF (iparg(8,ng) == 1) cycle
131 IF (max(1,jmult) < nm) cycle
132 ! pressurer rezoning for outlets (continuity)
133 IF( jmult /= 0) mtn =iparg(24+nm,ng)
134 IF (nvar == 10 .AND.(mtn == 37)) cycle
135 IF (nvar == 12 .AND. elbuf_str(ng)%GBUF%G_TEMP == 0) cycle
136 !-----------------------------!
137 irs=iparg(15,ng) !rezoning sigma enabled
138 ire=iparg(16,ng) !rezoning plasticity or burning time
139 lft=1
140 nel=llt
141
142 !----------------------------!
143 ! N V A R = 2 !
144 ! (SIGMA) !
145 !----------------------------!
146 IF (nvar == 2 .AND. irs == 1) THEN
147 IF (itrimat > 0 .AND. mtn == 51) THEN
148 add = m51_n0phas + (itrimat-1)*m51_nvphas + idx ! ADD+1 => SIG(1)
149 add = add *llt
150 DO i=lft,llt
151 j = i+nft
152 phi(j) = elbuf_str(ng)%BUFLY(1)%MAT(1,1,1)%VAR(add+i)
153 END DO
154 ELSE
155 DO i=lft,llt !other material laws or mtn=51
156 j = i+nft
157 k = (idx-1)*nel + i !idx : 1:6
158 phi(j) = elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%SIG(k)
159 ENDDO
160 ENDIF
161 !----------------------------!
162 ! N V A R = 10 !
163 ! (PLAS) !
164 ! (TB) explo. !
165 ! (RK) turb. !
166 !----------------------------!
167 ELSEIF (nvar == 10 .AND. ire == 1) THEN
168 IF (mtn == 41) cycle
169 IF (mtn==51) THEN !submat 4 is JWL
170 IF(itrimat==0)THEN
171 cycle
172 ELSEIF(itrimat <= 3)THEN
173 add0= m51_n0phas + (itrimat-1)*m51_nvphas
174 add = add0 + 15 ! PLAS
175 k = llt*(add-1)
176 var => elbuf_str(ng)%BUFLY(1)%MAT(1,1,1)%VAR(k+1:k+llt)
177 ELSEIF(itrimat == 4)THEN
178 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%TB(1:llt)
179 ENDIF
180 ELSEIF (mtn == 5 .OR. mtn ==97 .OR. mtn==105) THEN ! DETONATION TIME
181 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%TB(1:llt)
182 ELSEIF (mtn == 6) THEN
183 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%RK(1:llt)
184 ELSEIF (mtn >= 28 .AND. mtn /= 67 .AND. mtn /= 49) THEN
185 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%PLA(1:llt)
186 ELSE
187 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%PLA(1:llt)
188 ENDIF
189 DO i=lft,llt
190 j = i+nft
191 phi(j) = var(i)
192 ENDDO
193 !----------------------------!
194 ! N V A R = 11 !
195 ! (MAT/EOS %VAR) !
196 !----------------------------!
197 ELSEIF (nvar == 11) THEN
198 IF( flag_mat_eos == 1 ) THEN
199 ! MAT %VAR buffer
200 var => elbuf_str(ng)%BUFLY(nm)%MAT(1,1,1)%VAR(llt*(idx-1)+1:llt*(idx))
201 DO i=lft,llt
202 j = i+nft
203 phi(j) = var(i)
204 ENDDO
205 ELSEIF( flag_mat_eos == 2 )THEN
206 ! EOS %VAR buffer
207 var => elbuf_str(ng)%BUFLY(nm)%EOS(1,1,1)%VAR(llt*(idx-1)+1:llt*(idx))
208 DO i=lft,llt
209 j = i+nft
210 phi(j) = var(i)
211 ENDDO
212 ENDIF
213 !----------------------------!
214 ! N V A R = 12 !
215 ! (TEMP) !
216 !----------------------------!
217 ELSEIF (nvar == 12) THEN
218 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%TEMP(1:llt)
219 DO i=lft,llt
220 j = i+nft
221 phi(j) = var(i)
222 ENDDO
223 !----------------------------!
224 ! DEFAULT !
225 !----------------------------!
226 ELSE
227 DO i=lft,llt
228 j=i+nft
229 phi(j)=zero
230 ENDDO
231 ENDIF !(NVAR == 2 .AND. IRS == 1)
232 ENDDO ! NG
233C---------------------
234 CALL my_barrier
235C---------------------
236 !------------------------------------!
237 ! SPMD EXCHANGES !
238 !------------------------------------!
239 IF (nspmd > 1)THEN
240!$OMP SINGLE
241 CALL spmd_e1vois(phi,nercvois,nesdvois,lercvois,lesdvois,lencom )
242!$OMP END SINGLE
243 END IF
244
245
246C=======================================================================
247C REZONING DEPENDING ON NVAR VALUE
248C=======================================================================
249
250 DO ng=itask+1,ngroup,nthread
251C ALE ON / OFF
252 IF (iparg(76, ng) == 1) cycle ! --> OFF
253 CALL initbuf(iparg ,ng ,
254 2 mtn ,llt ,nft ,iad ,ity ,
255 3 npt ,jale ,ismstr ,jeul ,jtur ,
256 4 jthe ,jlag ,jmult ,jhbe ,jivf ,
257 5 nvaux ,jpor ,jcvt ,jclose ,jplasol ,
258 6 irep ,iint ,igtyp ,israt ,isrot ,
259 7 icsen ,isorth ,isorthg ,ifailure,jsms )
260 !-----------------------------!
261 ! UNPLUG CONDITIONS !
262 !-----------------------------!
263 nuvar_mat = iparg(81,ng)
264 nuvar_eos = iparg(82,ng)
265 IF (nvar == 11)THEN
266 IF (flag_mat_eos == 0 .OR. idx == 0) cycle ! %VAR (MAT and EOS)
267 IF(flag_mat_eos == 1)THEN
268 IF(idx > nuvar_mat) cycle ! rezon uvar( I, 1:NUVAR_MAT) only
269 ELSEIF (flag_mat_eos == 2)THEN
270 IF(idx > nuvar_eos) cycle ! rezon uvar( I, 1:NUVAR_MAT) only
271 ENDIF
272 ENDIF
273 IF (max(1,jmult) < nm) cycle
274 IF (jale+jeul == 0) cycle
275 IF (iparg(8,ng) == 1) cycle
276 IF (itrimat /= 0.AND.mtn /= 51) cycle
277 IF (jmult /= 0) mtn = iparg(24+nm,ng)
278 IF (nvar == 10 .AND. (mtn == 37)) cycle
279 IF (nvar == 10 .AND. mtn==51 .AND. itrimat == 0) cycle
280 IF (nvar == 12 .AND. elbuf_str(ng)%GBUF%G_TEMP == 0) cycle
281 !-----------------------------!
282 irs=iparg(15,ng)
283 ire=iparg(16,ng)
284 nel=llt
285 !----------------------------!
286 ! N V A R = 2 !
287 ! (sigma) !
288 !----------------------------!
289 IF (nvar == 2 .AND. irs == 1) THEN
290 indx = idx
291 IF (itrimat > 0) THEN
292 add = m51_n0phas + (itrimat-1)*m51_nvphas + idx ! ADD+1 => SIG[IDX](i=1)
293 add = add *llt
294 sig => elbuf_str(ng)%BUFLY(1)%MAT(1,1,1)%VAR(add+1:add+llt) ! S[INDX] , S1,S2,S3,...,or S6
295 add = m51_n0phas + (itrimat-1)*m51_nvphas + 10 ! ADD+1 => VOL(1)
296 add = add *llt
297 vol => elbuf_str(ng)%BUFLY(1)%MAT(1,1,1)%VAR(add+1:add+llt)
298 indx = 1
299 ELSE
300 sig => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%SIG(llt*(indx-1)+1:llt*idx)
301 vol => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%VOL(1:llt)
302 ENDIF
303 IF (n2d == 0) THEN
304 tag22 => elbuf_str(ng)%GBUF%TAG22(1:llt)
305 CALL arezo3(ale_connect,sig,phi,flux(6*nft+1),vol,tag22)
306 ELSE
307 nfx = nft+(nm-1)*numelq
308 IF (nmult == 0) THEN
309 CALL arezo2(ale_connect,sig,phi,flux(4*nfx+1),vol)
310 ELSE
311 CALL brezo2(ale_connect,sig ,phi,flux(4*nfx+1),vol,bhole,nm)
312 ENDIF
313 ENDIF
314 !----------------------------!
315 ! N V A R = 10 !
316 ! (PLAS) !
317 ! (TB) explo. !
318 ! (RK) turb. !
319 !----------------------------!
320 ELSEIF (nvar == 10 .AND. ire == 1) THEN
321 IF (mtn == 41) cycle
322 indx = idx
323 vol => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%VOL(1:llt)
324 IF (itrimat /= 0 .AND. itrimat /= 4)THEN
325 add0= m51_n0phas + (itrimat-1)*m51_nvphas
326 add = add0 + 15 ! UVAR(ADD+1) => PLAS
327 k = llt*(add-1)
328 var =>elbuf_str(ng)%BUFLY(1)%MAT(1,1,1)%VAR(k+1:k+llt)
329 indx=1
330 ELSEIF (mtn == 5 .OR. mtn == 97 .OR. mtn==105 .OR. itrimat == 4) THEN
331 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%TB(1:llt)
332 ELSEIF (mtn == 6) THEN
333 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%RK(1:llt)
334 ELSEIF (mtn >= 28 .AND. mtn /= 67 .AND. mtn /= 49) THEN
335 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%PLA(1:llt)
336 ELSE
337 var => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%PLA(1:llt)
338 ENDIF
339 IF (n2d == 0) THEN
340 tag22 => elbuf_str(ng)%GBUF%TAG22(1:llt)
341 CALL arezo3(ale_connect,var,phi,flux(6*nft+1),vol,tag22)
342 ELSE
343 nfx=nft+(nm-1)*numelq
344 IF(nmult == 0)THEN
345 CALL arezo2(ale_connect,var,phi,flux(4*nfx+1),vol)
346 ELSE
347 CALL brezo2(ale_connect,var,phi,flux(4*nfx+1),vol,bhole,nm)
348 ENDIF
349 ENDIF
350 !----------------------------!
351 ! N V A R = 11 !
352 ! (MAT/EOS %VAR) !
353 !----------------------------!
354 ELSEIF (nvar == 11) THEN
355 vol => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%VOL(1:llt)
356 IF(flag_mat_eos == 1)THEN
357 var => elbuf_str(ng)%BUFLY(nm)%MAT(1,1,1)%VAR(llt*(idx-1)+1:llt*(idx))
358 ELSEIF (flag_mat_eos == 2)THEN
359 var => elbuf_str(ng)%BUFLY(nm)%EOS(1,1,1)%VAR(llt*(idx-1)+1:llt*(idx))
360 ENDIF
361 DO i=lft,llt
362 j = i+nft
363 phi(j) = var(i)
364 ENDDO
365 IF (n2d == 0) THEN
366 tag22 => elbuf_str(ng)%GBUF%TAG22(1:llt)
367 CALL arezo3(ale_connect,var,phi,flux(6*nft+1),vol,tag22)
368 ELSE
369 nfx=nft+(nm-1)*numelq
370 IF(nmult == 0)THEN
371 CALL arezo2(ale_connect,var,phi,flux(4*nfx+1),vol)
372 ELSE
373 CALL brezo2(ale_connect,var,phi,flux(4*nfx+1),vol,bhole,nm)
374 ENDIF
375 ENDIF
376
377 !----------------------------!
378 ! N V A R = 12 !
379 ! (TEMP) !
380 !----------------------------!
381 ELSEIF (nvar == 12) THEN
382 indx = idx
383 temp => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%TEMP(1:llt)
384 vol => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%VOL(1:llt)
385 IF (itrimat /= 0) THEN
386 add0= m51_n0phas + (itrimat-1)*m51_nvphas
387 add = add0 + 16 ! UVAR(ADD+1) => TEMP
388 k = llt*(add-1)
389 temp =>elbuf_str(ng)%BUFLY(1)%MAT(1,1,1)%VAR(k+1:k+llt)
390 indx=1
391 ELSE
392 temp => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%TEMP(1:llt)
393 vol => elbuf_str(ng)%BUFLY(nm)%LBUF(1,1,1)%VOL(1:llt)
394 ENDIF
395 IF (n2d == 0) THEN
396 tag22 => elbuf_str(ng)%GBUF%TAG22(1:llt)
397 CALL arezo3(ale_connect,temp,phi,flux(6*nft+1),vol,tag22)
398 ELSE
399 nfx=nft+(nm-1)*numelq
400 IF(nmult == 0)THEN
401 CALL arezo2(ale_connect,temp,phi,flux(4*nfx+1),vol)
402 ELSE
403 CALL brezo2(ale_connect,temp,phi,flux(4*nfx+1),vol,bhole,nm)
404 ENDIF
405 ENDIF
406
407 ENDIF ! (NVAR == 2 .AND. IRS == 1)
408 ENDDO ! next NG
409 END DO !next NM
410C-----------
411 RETURN
412 END SUBROUTINE arezon
413 END MODULE arezon_mod
subroutine brezo2(ale_connect, var, phi, flux, vol, bhole, nm)
Definition brezo2.F:31
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
subroutine arezo2(ale_connect, var, phi, flux, vol)
Definition arezo2.F:38
subroutine arezo3(ale_connect, var, phi, flux, vol, iad22)
Definition arezo3.F:38
subroutine arezon(iparg, elbuf_str, flux, phi, ale_connect, nvar, nv, itask, nercvois, nesdvois, lercvois, lesdvois, lencom, bhole, itrimat, opt_flag_mat_eos)
Definition arezon.F:54
subroutine initbuf(iparg, ng, mtn, llt, nft, iad, ity, npt, jale, ismstr, jeul, jtur, jthe, jlag, jmult, jhbe, jivf, mid, jpor, jcvt, jclose, jpla, irep, iint, igtyp, israt, isrot, icsen, isorth, isorthg, ifailure, jsms)
Definition initbuf.F:261
subroutine spmd_e1vois(phi, nercvois, nesdvois, lercvois, lesdvois, lencom)
Definition spmd_cfd.F:375
subroutine my_barrier
Definition machine.F:31