OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
fvmesh0.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"
#include "scr17_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine fvmesh0 (t_monvol, xyzini, ixs, ixc, ixtg, pm, ipm, igrsurf, xyzref, nb_node)
subroutine applysort2fvm (t_monvol)

Function/Subroutine Documentation

◆ applysort2fvm()

subroutine applysort2fvm ( type(monvol_struct_), dimension(nvolu), intent(inout) t_monvol)

Definition at line 325 of file fvmesh0.F.

326C Description: Apply renumbering to FVMBAGS (ELTG et TBA)
327C after S*HEAD S*TAILS routines
328C-----------------------------------------------
329C M o d u l e s
330C-----------------------------------------------
331 USE fvbag_mod
333 USE reorder_mod
335C-----------------------------------------------
336C I m p l i c i t T y p e s
337C-----------------------------------------------
338#include "implicit_f.inc"
339C-----------------------------------------------
340C C o m m o n B l o c k s
341C-----------------------------------------------
342#include "com04_c.inc"
343#include "scr17_c.inc"
344C-----------------------------------------------
345C D u m m y A r g u m e n t s
346C-----------------------------------------------
347 TYPE(MONVOL_STRUCT_), DIMENSION(NVOLU), INTENT(INOUT) :: T_MONVOL
348C-----------------------------------------------
349C L o c a l V a r i a b l e s
350C-----------------------------------------------
351 INTEGER :: IFV, N, ITYP, NNS, NTG, NBA, NTGA, NNA, NNI, NTGI, NNT, IREF, ID, NTGT
352 INTEGER J, IEL
353 INTEGER, DIMENSION(:), ALLOCATABLE :: TMP
354C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
355 ifv=0
356 DO n = 1, nvolu
357 ityp = t_monvol(n)%TYPE
358 id = t_monvol(n)%ID
359 IF (ityp == 6 .OR. ityp == 8 .OR. ityp == 11) THEN
360 iref = t_monvol(n)%IVOLU(59)
361 ifv = ifv + 1
362 nns = t_monvol(n)%NNS
363 ntg = t_monvol(n)%NTG
364 nni = t_monvol(n)%NNI
365 ntgi = t_monvol(n)%NTGI
366 nba = t_monvol(n)%NBRIC
367 ntga = t_monvol(n)%NTGA
368 nna = t_monvol(n)%NNA
369 nnt = nns + nni
370 ntgt = ntg + ntgi
371
372C----------------------------------------------
373C Parametres de decoupage automatique du volume
374C----------------------------------------------
375C PERMUTATION ELTG
376 IF (ntg > 0) THEN
377 ALLOCATE(tmp(ntg))
378 DO j = 1, ntg
379 iel = t_monvol(n)%ELTG(j)
380 IF (iel <= numelc) THEN
381 tmp(j) = permutation%SHELL(iel + numelc)
382 ELSE IF (iel > numelc) THEN
383 tmp(j) = numelc + permutation%TRIANGLE(iel - numelc + numeltg)
384 ENDIF
385 ENDDO
386 t_monvol(n)%ELTG(1:ntg) = tmp(1:ntg)
387 DEALLOCATE(tmp)
388 ENDIF
389
390 IF (ntgi > 0) THEN
391 ALLOCATE(tmp(ntgi))
392 DO j = 1, ntgi
393 iel = t_monvol(n)%ELTG(ntg + j)
394 IF (iel <= numelc) THEN
395 tmp(j) = permutation%SHELL(iel + numelc)
396 ELSE IF (iel > numelc) THEN
397 tmp(j) = numelc + permutation%TRIANGLE(iel - numelc + numeltg)
398 ENDIF
399 ENDDO
400 t_monvol(n)%ELTG(ntg + 1: ntg + ntgi) = tmp(1:ntgi)
401 DEALLOCATE(tmp)
402 ENDIF
403
404C PERMUTATION TBA
405 IF (ntg > 0 .AND. (.NOT. tetramesher_used)) THEN
406 DO j = 1, nba
407 iel = t_monvol(n)%TBRIC(1, j)
408 t_monvol(n)%TBRIC(1, j) = permutation%SOLID(iel + numels)
409 ENDDO
410 ELSE IF(ntg > 0 .AND. tetramesher_used) THEN
411C Not possible
412 ENDIF
413 ENDIF
414 ENDDO
415C
416
417 RETURN
418C
initmumps id
type(reorder_struct_) permutation
Definition reorder_mod.F:54

◆ fvmesh0()

subroutine fvmesh0 ( type(monvol_struct_), dimension(nvolu), intent(inout) t_monvol,
xyzini,
integer, dimension(nixs,*) ixs,
integer, dimension(nixc,*) ixc,
integer, dimension(nixtg,*) ixtg,
pm,
integer, dimension(npropmi,*) ipm,
type (surf_), dimension(nsurf) igrsurf,
xyzref,
integer nb_node )

Definition at line 54 of file fvmesh0.F.

55C-----------------------------------------------
56C M o d u l e s
57C-----------------------------------------------
58 USE my_alloc_mod
59 USE fvbag_mod
61 USE reorder_mod
62 USE message_mod
63 USE groupdef_mod
66 USE fvelinte_mod , ONLY : fvelinte
67 USE fvvolu_mod , ONLY : fvvolu
68 USE fvinjnormal_mod , ONLY : fvinjnormal
69 USE fvlength_mod , ONLY : fvlength
70C-----------------------------------------------
71C I m p l i c i t T y p e s
72C-----------------------------------------------
73#include "implicit_f.inc"
74C-----------------------------------------------
75C C o m m o n B l o c k s
76C-----------------------------------------------
77#include "com01_c.inc"
78#include "com04_c.inc"
79#include "param_c.inc"
80#include "units_c.inc"
81#include "scr17_c.inc"
82C-----------------------------------------------
83C D u m m y A r g u m e n t s
84C-----------------------------------------------
85 TYPE(MONVOL_STRUCT_), DIMENSION(NVOLU), INTENT(INOUT) :: T_MONVOL
86 INTEGER IXS(NIXS,*), IXC(NIXC,*), IXTG(NIXTG,*)
87 INTEGER IPM(NPROPMI,*)
88 INTEGER NB_NODE
89 my_real xyzini(3,nb_node), pm(npropm,*), xyzref(3,nb_node)
90 TYPE (SURF_) , DIMENSION(NSURF) :: IGRSURF
91C-----------------------------------------------
92C L o c a l V a r i a b l e s
93C-----------------------------------------------
94 INTEGER IFV,
95 . N, ITYP, NNS, NTG, NBRIC, NBX, NBY, NNB,
96 . NBA, NTGA, NNA,
97 . PFLAG, NNI, NTGI, ILVOUT, NNFV, NNT, NSURFI,
98 . NSEG, IREF, NTRFV, NPOLH, ID,
99 . NTGT, INODE
100 INTEGER I
101 INTEGER IBID
102 CHARACTER(len=nchartitle) :: TITR
103 INTEGER, DIMENSION(:), ALLOCATABLE :: MINUS_SIGN_REVERSE
104 my_real, DIMENSION(:,:), ALLOCATABLE :: x
105 my_real dirx,diry,dirz,dir2x,dir2y,dir2z,origx,origy,origz,lx,ly,lz
106C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
107 CALL my_alloc(x,3,nb_node)
108 pflag = 0
109 ifv=0
110 DO n = 1, nvolu
111 ityp = t_monvol(n)%TYPE
112 id = t_monvol(n)%ID
113 titr = t_monvol(n)%TITLE
114 IF (ityp == 6 .OR. ityp == 8) THEN
115 IF (pflag == 0) THEN
116 WRITE(iout,1000)
117 pflag = 1
118 ENDIF
119C
120 iref = t_monvol(n)%IVOLU(59)
121 IF(iref==0) THEN
122 x=xyzini
123 ELSE
124 x=xyzref
125 ENDIF
126C
127 ifv=ifv+1
128 nns = t_monvol(n)%NNS
129 ntg = t_monvol(n)%NTG
130 nni = t_monvol(n)%NNI
131 ntgi = t_monvol(n)%NTGI
132 nba = t_monvol(n)%NBRIC
133 ntga = t_monvol(n)%NTGA
134 nna = t_monvol(n)%NNA
135 nnt = nns + nni
136 ntgt = ntg + ntgi
137
138 t_monvol(n)%KR5 = 1+nrvolu*nvolu+lrcbag+lrbagjet+lrbaghol+t_monvol(n)%IVOLU(34) + nnt*6
139C----------------------------------------------
140C Parametres de decoupage automatique du volume
141C----------------------------------------------
142 dirx = t_monvol(n)%RVOLU(35)
143 diry = t_monvol(n)%RVOLU(36)
144 dirz = t_monvol(n)%RVOLU(37)
145 dir2x = t_monvol(n)%RVOLU(38)
146 dir2y = t_monvol(n)%RVOLU(39)
147 dir2z = t_monvol(n)%RVOLU(40)
148 origx = t_monvol(n)%RVOLU(41)
149 origy = t_monvol(n)%RVOLU(42)
150 origz = t_monvol(n)%RVOLU(43)
151 lx = t_monvol(n)%RVOLU(44)
152 ly = t_monvol(n)%RVOLU(45)
153 lz = t_monvol(n)%RVOLU(53)
154 fvdata(ifv)%L_TYPE = 0
155 fvdata(ifv)%ID_DT_OPTION = t_monvol(n)%IVOLU(27)
156 fvdata(ifv)%LAMBDA = zero
157 fvdata(ifv)%DTOLD = zero
158 fvdata(ifv)%CFL_COEF = t_monvol(n)%RVOLU(71)
159 fvdata(ifv)%DTMIN = t_monvol(n)%RVOLU(72)
160 fvdata(ifv)%PDISP = zero
161 fvdata(ifv)%PDISP_OLD = zero
162C
163 CALL fvverif(
164 . ntga, t_monvol(n)%ELEMA, x, id,
165 . dirx, diry, dirz, dir2x, dir2y,
166 . dir2z, origx, origy, origz,
167 . lx, ly, lz, t_monvol(n)%NODES, t_monvol(n)%IBUFA, t_monvol(n)%TAGELA,
168 . titr)
169C
170 t_monvol(n)%RVOLU(44) = lx
171 t_monvol(n)%RVOLU(45) = ly
172 t_monvol(n)%RVOLU(53) = lz
173C
174 nbx = t_monvol(n)%IVOLU(54)
175 nby = t_monvol(n)%IVOLU(55)
176 nbric = nbx * nby
177 nnb = (nbx + 1) * (nby + 1) * 2
178 ALLOCATE(fvdata(ifv)%BRIC(8,nbric),
179 . fvdata(ifv)%TBRIC(13,nbric),
180 . fvdata(ifv)%XB(3,nnb),
181 . fvdata(ifv)%SFAC(6,4,nbric))
182C
183 CALL fvbric(t_monvol(n)%IVOLU, t_monvol(n)%RVOLU, t_monvol(n)%NODES, x, nns)
184C
185 t_monvol(n)%IVOLU(50) = t_monvol(n)%IVOLU(46)
186 t_monvol(n)%IVOLU(51) = t_monvol(n)%IVOLU(47)
187 t_monvol(n)%IVOLU(52) = t_monvol(n)%IVOLU(48)
188 t_monvol(n)%IVOLU(53) = t_monvol(n)%IVOLU(49)
189C
190 CALL fvmesh1(
191 . t_monvol(n)%NODES, t_monvol(n)%ELEM, x, t_monvol(n)%IVOLU, fvdata(ifv)%BRIC,
192 . fvdata(ifv)%XB, t_monvol(n)%RVOLU, ntg, ntgi, nbric, fvdata(ifv)%TBRIC,
193 . fvdata(ifv)%SFAC, fvdata(ifv)%DLH, nba, ntga,
194 . t_monvol(n)%TBRIC, t_monvol(n)%TFAC, t_monvol(n)%TAGELS, t_monvol(n)%IBUFA,
195 . t_monvol(n)%ELEMA, t_monvol(n)%TAGELA, ixs, id ,titr, nb_node, ityp)
196
197 IF (kmesh(n) >= 2) THEN
198 t_monvol(n)%KRA5 = 1 + nrvolu * nvolu + lrcbag + lrbagjet + lrbaghol +
199 . t_monvol(n)%IVOLU(34) + 7*nnt+4*ntgt+6*nna
200 t_monvol(n)%VELOCITY(1:3, 1:nna) = zero
201 DO i = 1, nna
202 inode = t_monvol(n)%IBUFA(i)
203 t_monvol(n)%NODE_COORD(1, i) = node_coord(1, inode)
204 t_monvol(n)%NODE_COORD(2, i) = node_coord(2, inode)
205 t_monvol(n)%NODE_COORD(3, i) = node_coord(3, inode)
206 ENDDO
207 ENDIF
208C
209 IF (ntgi > 0) THEN
210 ilvout = t_monvol(n)%IVOLU(44)
211 nsurfi=t_monvol(n)%INT_SURFID
212 nseg=igrsurf(nsurfi)%NSEG
213C-----------------------------
214C Elements de surface interne
215C-----------------------------
216 t_monvol(n)%POROSITY(1:ntgi) = zero
217 CALL fvelinte(t_monvol(n)%NODES, t_monvol(n)%ELEM(1, ntg + 1), ixc, ixtg,
218 . pm, ipm, ilvout, ifv, nnt, ntg, t_monvol(n)%POROSITY,
219 . nseg,igrsurf(nsurfi)%ELTYP, ntgi, t_monvol(n)%ELTG,
220 . nb_node,igrsurf(nsurfi)%ELEM)
221C--------------------------------
222C Injecteurs sur surface interne
223C--------------------------------
224 ALLOCATE(minus_sign_reverse(ntgi))
225 minus_sign_reverse(:) = 0
226 CALL fvinjectint(
227 . t_monvol(n)%NODES, t_monvol(n)%ELEM(1, ntg + 1), t_monvol(n)%IBAGJET,
228 . t_monvol(n)%NJET , igrsurf ,
229 . t_monvol(n)%ITAGEL(ntg + 1), nns+nni , ntgi,nb_node,
230 . minus_sign_reverse)
231C--------------------------------
232C Porous surface sur surface interne
233C--------------------------------
234 CALL fvventholeint(
235 . t_monvol(n)%NODES, t_monvol(n)%ELEM(1, ntg + 1), t_monvol(n)%IBAGHOL,
236 . t_monvol(n)%NVENT, igrsurf ,
237 . t_monvol(n)%ITAGEL(ntg + 1), nns+nni , ntgi, nb_node)
238C
239 CALL fvelsurf(
240 . t_monvol(n)%NODES, t_monvol(n)%ELEM(1, ntg + 1), ibid, ixc, ixtg, ntgi,
241 . t_monvol(n)%ELTG(ntg + 1), t_monvol(n)%MATTG(ntg + 1), nb_node, .false.)
242C-----------------------------------------------------------------------
243C REDEFINE INTERNAL TRIANGLE FOR NORMAL CONSISTENCY FOR INJECTORS
244C-----------------------------------------------------------------------
245 CALL fvinjnormal(
246 . t_monvol(n)%NODES, t_monvol(n)%ELEM(1, ntg + 1), ixc, ixtg,
247 . t_monvol(n)%ELTG(ntg + 1), ntgi, ilvout,
248 . minus_sign_reverse)
249 DEALLOCATE(minus_sign_reverse)
250 CALL fvelprint(
251 . ixc, ixtg, ntgi, t_monvol(n)%ITAGEL(ntg + 1), t_monvol(n)%ELTG(ntg + 1),
252 . t_monvol(n)%IBAGHOL, ilvout , 1 )
253C------------------------------------------------------
254C Tag element interne pour l'option /TH/SURF mass flow
255C------------------------------------------------------
256 DO i=1,nsurf
257 nseg=igrsurf(i)%NSEG
258 CALL fvthsurf(nseg, ntgi,igrsurf(i)%ELTYP, t_monvol(n)%ELTG(ntg + 1),
259 . t_monvol(n)%THSURF_TAG(i, 1:ntgi + 1), igrsurf(i)%ELEM)
260 ENDDO
261 ENDIF
262C---------------------------------
263C Noeuds de briques additionnelles
264C---------------------------------
265 IF (nna > 0) THEN
266 nnfv = t_monvol(n)%IVOLU(46)
267 CALL fvnodbr(t_monvol(n)%IBUFA, nna, nnfv, ifv, nb_node)
268 ENDIF
269C
270 nnfv = t_monvol(n)%IVOLU(46)
271 ntrfv = t_monvol(n)%IVOLU(47)
272 npolh = t_monvol(n)%IVOLU(49)
273C------------------------------------
274C REFERENCE METRICS : VOLUME CHECK
275C------------------------------------
276 IF (iref /= 0) THEN
277 CALL fvvolu( ityp, nnfv, ntrfv, npolh,
278 1 t_monvol(n)%NODES, t_monvol(n)%IBUFA, t_monvol(n)%ELEMA, t_monvol(n)%TAGELA,
279 2 xyzini, t_monvol(n)%IVOLU, t_monvol(n)%RVOLU,
280 3 fvdata(ifv)%IFVNOD, fvdata(ifv)%RFVNOD, fvdata(ifv)%IFVTRI,
281 4 fvdata(ifv)%IFVPOLY,fvdata(ifv)%IFVTADR,fvdata(ifv)%IFVPOLH,
282 5 fvdata(ifv)%IFVPADR,fvdata(ifv)%MPOLH,
283 6 fvdata(ifv)%EPOLH, fvdata(ifv)%VPOLH_INI )
284C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
285
286 ENDIF
287C----------------------------------------
288C COMPUTE MINIMUM LENGTH FOR TIME STEP
289C----------------------------------------
290 CALL fvlength(nnfv, ntrfv, npolh,
291 1 t_monvol(n)%NODES, t_monvol(n)%IBUFA, t_monvol(n)%ELEMA, t_monvol(n)%TAGELA,
292 2 xyzini, t_monvol(n)%IVOLU,
293 3 fvdata(ifv)%IFVNOD, fvdata(ifv)%RFVNOD, fvdata(ifv)%IFVTRI,
294 4 fvdata(ifv)%IFVPOLY,fvdata(ifv)%IFVTADR,fvdata(ifv)%IFVPOLH,
295 5 fvdata(ifv)%IFVPADR,fvdata(ifv)%IBPOLH, fvdata(ifv)%DLH )
296C----------------------------
297C COMPUTE INITIAL SURFACE
298C----------------------------
299 CALL fvelarea(t_monvol(n)%NODES, t_monvol(n)%ELEM, xyzref, ntgt,
300 1 t_monvol(n)%ELAREA)
301C
302 ENDIF
303 ENDDO
304C
305 DEALLOCATE(x)
306 RETURN
307C
3081000 FORMAT(
309 . //,' FVMBAG: FINITE VOLUME MESH '/
310 . ' -------------------------- ')
311C
#define my_real
Definition cppsort.cpp:32
subroutine fvelarea(ibuf, elem, x, nel, elarea)
Definition fvelarea.F:32
subroutine fvelprint(ixc, ixtg, nel, itagel, eltg, ibaghol, ilvout, iflag)
Definition fvelprint.F:31
subroutine fvelsurf(ibuf, elem, elem_id, ixc, ixtg, nel, eltg, mattg, nb_node, flag)
Definition fvelsurf.F:32
subroutine fvinjectint(ibuf, elem, ibagjet, njet, igrsurf, itagel, nn, nel, nb_node, minus_sign_reverse)
Definition fvinjectint.F:32
subroutine fvverif(nela, elema, x, monvid, vx3, vy3, vz3, vx1, vy1, vz1, xb0, yb0, zb0, lx, ly, lz, ibuf, ibufa, tagela, titr)
Definition fvmbag1.F:278
subroutine fvnodbr(ibufa, nna, nnfv, ifv, nb_node)
Definition fvmbag1.F:530
subroutine fvthsurf(nseg, ntgi, surf_eltyp, eltg, itag, surf_elem)
Definition fvthsurf.F:29
subroutine fvventholeint(ibuf, elem, ibaghol, nvent, igrsurf, itagel, nn, nel, nb_node)
type(fvbag_data), dimension(:), allocatable fvdata
Definition fvbag_mod.F:128
subroutine fvelinte(ibuf, elem, ixc, ixtg, pm, ipm, ilvout, ifv, nnt, ntg, porosity, nseg, surf_eltyp, ntgi, eltg, nb_node, surf_elem)
Definition fvelinte.F:40
subroutine fvinjnormal(ibuf, elem, ixc, ixtg, eltg, nel, ilvout, minus_sign_reverse)
Definition fvinjnormal.F:37
subroutine fvlength(nns, nntr, npolh, ibuf, ibufa, elema, tagela, x, ivolu, ifvnod, rfvnod, ifvtri, ifvpoly, ifvtadr, ifvpolh, ifvpadr, ibpolh, dlh)
Definition fvlength.F:43
integer, dimension(:), allocatable kmesh
subroutine fvvolu(ityp, nns, nntr, npolh, ibuf, ibufa, elema, tagela, x, ivolu, rvolu, ifvnod, rfvnod, ifvtri, ifvpoly, ifvtadr, ifvpolh, ifvpadr, mpolh, epolh, vpolh_ini)
Definition fvvolu.F:44
integer, parameter nchartitle
subroutine fvbric(ivolu, rvolu, ibuf, x, nn)
Definition fvbric.F:31
subroutine fvmesh1(ibuf, elem, x, ivolu, bric, xb, rvolu, nel, neli, nbric, tbric, sfac, dxm, nba, nela, tba, tfaca, tagels, ibufa, elema, tagela, ixs, id, titr, nb_node, ityp)
Definition fvmesh.F:53