54 SUBROUTINE fvmesh0(T_MONVOL, XYZINI, IXS, IXC, IXTG, PM,IPM, IGRSURF, XYZREF,NB_NODE)
73#include "implicit_f.inc"
86 INTEGER IXS(NIXS,*), IXC(NIXC,*), IXTG(NIXTG,*)
87 INTEGER IPM(NPROPMI,*)
89 my_real xyzini(3,nb_node), pm(npropm,*), xyzref(3,nb_node)
90 TYPE (SURF_) ,
DIMENSION(NSURF) :: IGRSURF
95 . N, ITYP, NNS, NTG, NBRIC, NBX, NBY, NNB,
97 . PFLAG, NNI, NTGI, ILVOUT, NNFV, NNT, NSURFI,
98 . NSEG, IREF, NTRFV, NPOLH, ID,
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
107 CALL my_alloc(x,3,nb_node)
111 ityp = t_monvol(n)%TYPE
113 titr = t_monvol(n)%TITLE
114 IF (ityp == 6 .OR. ityp == 8)
THEN
120 iref = t_monvol(n)%IVOLU(59)
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
138 t_monvol(n)%KR5 = 1+nrvolu*nvolu+lrcbag+lrbagjet+lrbaghol+t_monvol(n)%IVOLU(34) + nnt*6
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
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
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,
170 t_monvol(n)%RVOLU(44) = lx
171 t_monvol(n)%RVOLU(45) = ly
172 t_monvol(n)%RVOLU(53) = lz
174 nbx = t_monvol(n)%IVOLU(54)
175 nby = t_monvol(n)%IVOLU(55)
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))
183 CALL fvbric(t_monvol(n)%IVOLU, t_monvol(n)%RVOLU, t_monvol(n)%NODES, x, nns)
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)
191 . t_monvol(n)%NODES, t_monvol(n)%ELEM, x, t_monvol(n)%IVOLU,
fvdata
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)
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
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)
210 ilvout = t_monvol(n)%IVOLU(44)
211 nsurfi=t_monvol(n)%INT_SURFID
212 nseg=igrsurf(nsurfi)%NSEG
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)
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)
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)
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.)
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 )
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)
266 nnfv = t_monvol(n)%IVOLU(46)
267 CALL fvnodbr(t_monvol(n)%IBUFA, nna, nnfv, ifv, nb_node)
270 nnfv = t_monvol(n)%IVOLU(46)
271 ntrfv = t_monvol(n)%IVOLU(47)
272 npolh = t_monvol(n)%IVOLU(49)
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,
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,
299 CALL fvelarea(t_monvol(n)%NODES, t_monvol(n)%ELEM, xyzref, ntgt,
300 1 t_monvol(n)%ELAREA)
309 . //,
' FVMBAG: FINITE VOLUME MESH '/
310 .
' -------------------------- ')