55
56
57
58 USE my_alloc_mod
70
71
72
73#include "implicit_f.inc"
74
75
76
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"
82
83
84
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
91
92
93
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,
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
106
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
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
119
120 iref = t_monvol(n)%IVOLU(59)
121 IF(iref==0) THEN
122 x=xyzini
123 ELSE
124 x=xyzref
125 ENDIF
126
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
139
140
141
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)
155 fvdata(ifv)%ID_DT_OPTION = t_monvol(n)%IVOLU(27)
158 fvdata(ifv)%CFL_COEF = t_monvol(n)%RVOLU(71)
159 fvdata(ifv)%DTMIN = t_monvol(n)%RVOLU(72)
161 fvdata(ifv)%PDISP_OLD = zero
162
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)
169
170 t_monvol(n)%RVOLU(44) = lx
171 t_monvol(n)%RVOLU(45) = ly
172 t_monvol(n)%RVOLU(53) = lz
173
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),
181 .
fvdata(ifv)%SFAC(6,4,nbric))
182
183 CALL fvbric(t_monvol(n)%IVOLU, t_monvol(n)%RVOLU, t_monvol(n)%NODES, x, nns)
184
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)
189
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,
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
208
209 IF (ntgi > 0) THEN
210 ilvout = t_monvol(n)%IVOLU(44)
211 nsurfi=t_monvol(n)%INT_SURFID
212 nseg=igrsurf(nsurfi)%NSEG
213
214
215
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)
221
222
223
224 ALLOCATE(minus_sign_reverse(ntgi))
225 minus_sign_reverse(:) = 0
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)
231
232
233
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)
238
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.)
242
243
244
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)
251 . ixc, ixtg, ntgi, t_monvol(n)%ITAGEL(ntg + 1), t_monvol(n)%ELTG(ntg + 1),
252 . t_monvol(n)%IBAGHOL, ilvout , 1 )
253
254
255
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
262
263
264
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
269
270 nnfv = t_monvol(n)%IVOLU(46)
271 ntrfv = t_monvol(n)%IVOLU(47)
272 npolh = t_monvol(n)%IVOLU(49)
273
274
275
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,
284
285
286 ENDIF
287
288
289
291 1 t_monvol(n)%NODES, t_monvol(n)%IBUFA, t_monvol(n)%ELEMA, t_monvol(n)%TAGELA,
292 2
296
297
298
299 CALL fvelarea(t_monvol(n)%NODES, t_monvol(n)%ELEM, xyzref, ntgt,
300 1 t_monvol(n)%ELAREA)
301
302 ENDIF
303 ENDDO
304
305 DEALLOCATE(x)
306 RETURN
307
3081000 FORMAT(
309 . //,' FVMBAG: FINITE VOLUME MESH '/
310 . ' -------------------------- ')
311
subroutine fvelarea(ibuf, elem, x, nel, elarea)
subroutine fvelprint(ixc, ixtg, nel, itagel, eltg, ibaghol, ilvout, iflag)
subroutine fvelsurf(ibuf, elem, elem_id, ixc, ixtg, nel, eltg, mattg, nb_node, flag)
subroutine fvinjectint(ibuf, elem, ibagjet, njet, igrsurf, itagel, nn, nel, nb_node, minus_sign_reverse)
subroutine fvverif(nela, elema, x, monvid, vx3, vy3, vz3, vx1, vy1, vz1, xb0, yb0, zb0, lx, ly, lz, ibuf, ibufa, tagela, titr)
subroutine fvnodbr(ibufa, nna, nnfv, ifv, nb_node)
subroutine fvthsurf(nseg, ntgi, surf_eltyp, eltg, itag, surf_elem)
subroutine fvventholeint(ibuf, elem, ibaghol, nvent, igrsurf, itagel, nn, nel, nb_node)
type(fvbag_data), dimension(:), allocatable fvdata
subroutine fvelinte(ibuf, elem, ixc, ixtg, pm, ipm, ilvout, ifv, nnt, ntg, porosity, nseg, surf_eltyp, ntgi, eltg, nb_node, surf_elem)
subroutine fvinjnormal(ibuf, elem, ixc, ixtg, eltg, nel, ilvout, minus_sign_reverse)
subroutine fvlength(nns, nntr, npolh, ibuf, ibufa, elema, tagela, x, ivolu, ifvnod, rfvnod, ifvtri, ifvpoly, ifvtadr, ifvpolh, ifvpadr, ibpolh, dlh)
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)
integer, parameter nchartitle
subroutine fvbric(ivolu, rvolu, ibuf, x, nn)
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)