OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
ale51_upwind3_int22.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!|| ale51_upwind3_int22 ../engine/source/ale/alefvm/cut_cells/ale51_upwind3_int22.F
25!||--- called by ------------------------------------------------------
26!|| afluxt ../engine/source/ale/ale51/afluxt.F
27!|| ale51_finish ../engine/source/ale/ale51/ale51_finish.F
28!|| ale51_init ../engine/source/ale/ale51/ale51_init.F
29!||--- calls -----------------------------------------------------
30!|| my_barrier ../engine/source/system/machine.F
31!||--- uses -----------------------------------------------------
32!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
33!|| i22bufbric_mod ../common_source/modules/interfaces/cut-cell-search_mod.F
34!|| i22tri_mod ../common_source/modules/interfaces/cut-cell-search_mod.F
35!|| multimat_param_mod ../common_source/modules/multimat_param_mod.F90
36!||====================================================================
38 . PM , IXS , ITRIMAT, IFLG ,
39 . IPARG , ELBUF_TAB, ITASK )
40C-----------------------------------------------
41C D e s c r i p t i o n
42C-----------------------------------------------
43C 'alefvm' is related to a collocated scheme (built from FVM and based on Godunov scheme)
44C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
45C This cut cell method is not completed, abandoned, and is not an official option.
46C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
47C
48C This subroutines computes from direct fluxes :
49C -1- FLUXES
50C -2- QMV(7:12) : QMV*DT = OUTGOING VOLUME (DT*FLUX(i,i) is INCOMING ONE), FLU1 IS SUM OF QMV
51C -3- DDVOL : D/DV . D/DT . VOL = DV/DT
52C
53C-----------------------------------------------
54C M o d u l e s
55C-----------------------------------------------
57 USE i22tri_mod
58 USE elbufdef_mod
59 USE multimat_param_mod , ONLY : m51_n0phas, m51_nvphas
60C-----------------------------------------------
61C I m p l i c i t T y p e s
62C-----------------------------------------------
63#include "implicit_f.inc"
64C-----------------------------------------------
65C G l o b a l P a r a m e t e r s
66C-----------------------------------------------
67#include "mvsiz_p.inc"
68C-----------------------------------------------
69C C o m m o n B l o c k s
70C-----------------------------------------------
71#include "com01_c.inc"
72#include "vect01_c.inc"
73#include "param_c.inc"
74#include "inter22.inc"
75#include "task_c.inc"
76C-----------------------------------------------
77C D u m m y A r g u m e n t s
78C-----------------------------------------------
79 INTEGER,INTENT(IN) :: ITRIMAT,IFLG
80 INTEGER IXS(NIXS,*), IPARG(NPARG,*),ITASK
81 my_real :: pm(npropm,*)
82 TYPE(elbuf_struct_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
83C-----------------------------------------------
84C L o c a l V a r i a b l e s
85C-----------------------------------------------
86 INTEGER :: J,K,ISILENT, MLW, MAT
87 my_real :: REDUC
88 INTEGER :: NBF,NBL, MCELL,ICELLv
89 INTEGER :: NUM, NADJ, IADJ, JV, NG
90
91 INTEGER :: IB,IBv, NIN, ICELL,NCELL,IDLOC
92 INTEGER :: IE,IDV,ADD, IE_M
93 my_real :: cellflux(6,9,nb),upwl(6)
94
95 my_real, DIMENSION(:), POINTER :: uvar,pddvol
96 my_real :: ddvol
97
98 LOGICAL :: debug_outp
99C-----------------------------------------------
100C P r e - C o n d i t i o n s
101C-----------------------------------------------
102 IF(trimat==0)RETURN
103 IF(int22==0)RETURN
104C-----------------------------------------------
105C S o u r c e L i n e s
106C-----------------------------------------------
107
108 !=================
109 ! INITIALIZATIONS
110 !=================
111 nin = 1
112 nbf = 1+itask*nb/nthread
113 nbl = (itask+1)*nb/nthread
114 nbl = min(nbl,nb)
115
116
117 !INTERFACE 22 ONLY - OUTPUT---------------!
118 debug_outp = .false.
119 if(ibug22_upwind/=0)then
120 if(ibug22_upwind>0)then
121 do ib=nbf,nbl
122 ie = brick_list(nin,ib)%id
123 mlw = brick_list(nin,ib)%mlw
124 if(ixs(11,ie)==ibug22_upwind)debug_outp=.true.
125 if(mlw/=51)debug_outp=.false.
126 enddo
127 elseif(ibug22_upwind==-1)then
128 debug_outp = .true.
129 endif
130 if(((itrimat/=ibug22_itrimat).and.(ibug22_itrimat/=-1)))debug_outp=.false.
131 endif
132 if(debug_outp)then
133 print *, " |----ale51_upwind3_int22.F-----|"
134 print *, " | THREAD INFORMATION |"
135 print *, " |------------------------------|"
136 print *, " NCYCLE =", ncycle
137 print *, " ITRIMAT=", itrimat
138 endif
139
140 !======================================================!
141 ! STEP B : NON CONFORM MESH !
142 ! USE CONSISTENT FLUX !
143 !======================================================!
144 DO ib=nbf,nbl
145 ie = brick_list(nin,ib)%ID
146 mlw = brick_list(nin,ib)%MLW
147 ncell = brick_list(nin,ib)%NBCUT
148 mcell = brick_list(nin,ib)%MainID
149 icell = 0
150 idloc = brick_list(nin,ib)%IDLOC
151 IF(mlw/=51)cycle
152 DO WHILE (icell<=ncell) ! loop on polyhedron {1:NCELL} U {9}
153 icell = icell +1
154 IF (icell>ncell .AND. ncell/=0)icell=9
155 !======================================================!
156 ! MULTIMATERIAL UPWIND TREATMENT !
157 !======================================================!
158 ie_m = brick_list(nin,ib)%POLY(icell)%WhereIsMain(3)
159 mat = ixs(1,ie_m)
160 upwl(1:6) = pm(16,mat)
161 reduc = pm(92,mat)
162 ddvol = zero
163 brick_list(nin,ib)%POLY(icell)%Adjacent_FLU1 = zero
164 DO j=1,6
165 nadj = brick_list(nin,ib)%POLY(icell)%FACE(j)%NAdjCell
166 DO iadj = 1,nadj
167 idv = brick_list(nin,ib)%Adjacent_Brick(j,1)
168 ibv = brick_list(nin,ib)%Adjacent_Brick(j,4)
169 jv = brick_list(nin,ib)%Adjacent_Brick(j,5)
170 icellv = brick_list(nin,ib)%POLY(icell)%FACE(j)%Adjacent_Cell(iadj)
171 cellflux(j,icell,ib) = brick_list(nin,ib)%POLY(icell)%FACE(j)%Adjacent_UpwFLUX(iadj)
172 IF(idv==0)THEN
173 cellflux(j,icell,ib)=cellflux(j,icell,ib)*reduc
174 ELSEIF(idv>0)THEN
175 ng = brick_list(nin,ib)%NG
176 isilent = iparg(64,ng)
177 IF(isilent==1)THEN
178 upwl(j)=one
179 cellflux(j,icell,ib)=cellflux(j,icell,ib)*pm(92,ixs(1,idv))
180 ENDIF
181 ENDIF
182 brick_list(nin,ib)%POLY(icell)%FACE(j)%Adjacent_upwFLUX(iadj) = cellflux(j,icell,ib)-upwl(j)*abs(cellflux(j,icell,ib))
183 brick_list(nin,ib)%POLY(icell)%Adjacent_FLU1 =
184 . brick_list(nin,ib)%POLY(icell)%Adjacent_FLU1 + cellflux(j,icell,ib)+upwl(j)*abs(cellflux(j,icell,ib))
185 IF(iflg==10)THEN
186 ddvol = ddvol + cellflux(j,icell,ib)
187C DDVOL = DDVOL + cellFLUX(J,ICELL,IB)+UPWL(J)*ABS(cellFLUX(J,ICELL,IB))
188C DDVOL = DDVOL + cellFLUX(J,ICELL,IB)-UPWL(J)*ABS(cellFLUX(J,ICELL,IB))
189 !DDVOL*DT IS SUM FOR INCOMING AND OUTCOMING VOLUMES. 2 * Sum(Nadj(j),j=1..6)
190 ENDIF
191 enddo!next IADJ
192 enddo!next J
193
194 brick_list(nin,ib)%POLY(icell)%DDVOL_upw = ddvol !HALF*DDVOL
195
196 !INTERFACE 22 ONLY - OUTPUT---------------!
197!#!include "lockon.inc"
198 if(debug_outp)then
199 if(ibug22_upwind==ixs(11,ie) .OR. ibug22_upwind==-1)then
200 print *, " brique =", ixs(11,ie)
201 print *, " icell =", icell
202 write (*,fmt='(A,1E26.14)') " Flu1 =", brick_list(nin,ib)%POLY(icell)%Adjacent_FLU1
203 DO j=1,6
204 nadj = brick_list(nin,ib)%POLY(icell)%FACE(j)%NAdjCell
205 DO iadj = 1,nadj
206 print *, " FACE =", j
207 write (*,fmt='(A,6E26.14)') " Flux(IAD:NADJ) =", brick_list(nin,ib)%POLY(icell)%FACE(j)%Adjacent_upwFLUX(iadj)
208 ENDDO
209 ENDDO
210 print *, " ------------------------"
211!#!include "lockoff.inc"
212 endif
213 endif
214
215
216 !======================================================!
217 enddo!next ICELL
218 enddo!next IB
219
220 !==============!
221 CALL my_barrier
222 !==============!
223
224 !---------------------------------------------------------!
225 ! SECND CELLS STACK !
226 !---------------------------------------------------------!
227 !STACK Secnd cells values from ones connected to current main cell
228 nin = 1
229 DO ib=nbf,nbl
230 ng = brick_list(nin,ib)%NG
231 ie = brick_list(nin,ib)%ID
232 idloc = brick_list(nin,ib)%IDLOC
233 mlw = brick_list(nin,ib)%MLW
234 num = brick_list(nin,ib)%SecndList%Num
235 mcell = brick_list(nin,ib)%mainID
236 IF(mlw/=51)cycle
237 ddvol = zero
238 DO k=1,num
239 ibv = brick_list(nin,ib)%SecndList%IBV(k)
240 icellv = brick_list(nin,ib)%SecndList%ICELLv(k)
241 ddvol = ddvol + brick_list(nin,ibv)%POLY(icellv)%DDVOL_upw
242 ENDDO
243 ddvol = ddvol + brick_list(nin,ib)%POLY(mcell)%DDVOL_upw
244 !updating law51 material buffer with computed stacked value
245 IF(itrimat>0)THEN
246 lft = 1
247 llt = iparg(2,ng)
248 uvar => elbuf_tab(ng)%BUFLY(1)%MAT(1,1,1)%VAR
249 add = (m51_n0phas + (itrimat-1)*m51_nvphas+12)*llt
250 pddvol => uvar(add+1:add+llt)
251 pddvol(idloc) = ddvol !*HALF : deja applique facteur 1/2
252 if(ixs(11,ie)==26354)then
253 print *, "itrimat, ddvoli", itrimat, ddvol
254 endif
255 ELSE
256 brick_list(nin,ib)%POLY(mcell)%DDVOL_upw = ddvol
257 ENDIF
258 enddo!next IB
259
260
261 RETURN
262 END
263C
subroutine ale51_upwind3_int22(pm, ixs, itrimat, iflg, iparg, elbuf_tab, itask)
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
type(brick_entity), dimension(:,:), allocatable, target brick_list
subroutine my_barrier
Definition machine.F:31