OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
flow0.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "com08_c.inc"
#include "param_c.inc"
#include "scr07_c.inc"
#include "flowcom.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine flow0 (iflow, rflow, wiflow, wrflow, x, v, a, npc, tf, sensor_tab, nbgauge, lgauge, gauge, nsensor, igrv, agrv, nfunct, python, wfext)

Function/Subroutine Documentation

◆ flow0()

subroutine flow0 ( integer, dimension(*) iflow,
rflow,
integer, dimension(*) wiflow,
wrflow,
x,
v,
a,
integer, dimension(*) npc,
tf,
type (sensor_str_), dimension(nsensor) sensor_tab,
integer, intent(in) nbgauge,
integer, dimension(3,*) lgauge,
gauge,
integer, intent(in) nsensor,
integer, dimension(nigrv,*) igrv,
agrv,
integer, intent(in) nfunct,
type (python_), intent(inout) python,
double precision, intent(inout) wfext )

Definition at line 36 of file flow0.F.

40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE sensor_mod
44 USE anim_mod
45 USE python_funct_mod
46C-----------------------------------------------
47C I m p l i c i t T y p e s
48C-----------------------------------------------
49#include "implicit_f.inc"
50C-----------------------------------------------
51C C o m m o n B l o c k s
52C-----------------------------------------------
53#include "com01_c.inc"
54#include "com08_c.inc"
55#include "param_c.inc"
56#include "scr07_c.inc"
57#include "flowcom.inc"
58C-----------------------------------------------
59C D u m m y A r g u m e n t s
60C-----------------------------------------------
61 INTEGER ,INTENT(IN) :: NSENSOR,NBGAUGE,NFUNCT
62 INTEGER IFLOW(*), WIFLOW(*), NPC(*),LGAUGE(3,*)
63 INTEGER IGRV(NIGRV,*)
64 my_real rflow(*), wrflow(*), x(3,*), v(3,*), a(3,*), tf(*), gauge(llgauge,*), agrv(lfacgrv,*)
65 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) :: SENSOR_TAB
66 TYPE (PYTHON_), INTENT(INOUT) :: PYTHON
67 DOUBLE PRECISION,INTENT(INOUT) :: WFEXT
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER IADI, IADR, I, ITYP, NINOUT, NNO, NEL, NNN, NEL_LOC,
72 . II1, II2, II3, II4, II5, II6, II7, IR1, IR2, IR3, IR4,
73 . IR5, IR6, IR7, IR8, IR9, IR10, IR11, II8, II9, II10, II11, IADIP, IADH, IADG,
74 . II12, II13, II14, IPINT, NDIM, JFORM, FREESURF
75C-----------------------------------------------------------------------------------
76C Description des tableaux ITYP=1
77C II1 -> IFLOW : parametres entiers
78C II2 -> IBUF : correspondances local-global noeuds surface
79C II3 -> ELEM : connectivite locale des triangles
80C II4 -> IINOUT : variables entieres pour les surfaces entrees-sorties
81C II5 -> IBUFI : correspondance local-global noeuds internes
82C II6 -> ITAGEL : tag des elements des surfaces d'entrees-sorties
83C----- tableaux SPMD
84C II7 -> IBUFR : indice ligne noeud local (0 si pas sur ce proc)
85C II8 -> IBUFC : indice colonne noeud local (0 si pas sur ce proc)
86C II9 -> IBUFL : liste noeuds surface sur processeur courant pour X, V, A
87C II10 -> CNP : attribution processeur pour noeuds surface pour X, V, A
88C II11 -> IBUFIL : liste noeuds internes sur processeur courant pour X, V, A
89C II12 -> CNPI : attribution processeur pour noeuds internes pour X, V, A
90C II13 -> IBUFELR : indice ligne elem local (0 si pas sur ce proc)
91C II14 -> IBUFELC : indice colonne elem local (0 si pas sur ce proc)
92C
93C IR1 -> RFLOW : parametres reels
94C IR2 -> PHI : potentiel
95C IR3 -> PRES : pression
96C IR4 -> U : vitesse
97C IR5 -> RINOUT : variables reelles pour les surfaces entrees-sorties
98C-----------------------------------------------------------------------------------
99C Description des tableaux ITYP=3
100C II1 -> IFLOW : parametres entiers
101C II2 -> IBUF : correspondances local-global noeuds surface
102C II3 -> ELEM : connectivite locale des triangles/quadrangles+flag
103C II4 -> IBUF_L : correspondances local-global noeuds surface (a supprimer en SPMD)
104C II5 -> SHELL_GA: correspondances local shell-gauge
105C II6 -> CNP : SPMD nombre de processeur pour chaque noeud
106C engine
107C II7 -> IPIV : lapack resolution nel > nelmax
108C II8 -> IBUFELR : SPMD
109C II9 -> IBUFELC : SPMD
110C
111C IR1 -> RFLOW : parametres reels
112C IR2 -> NORMAL : normale
113C IR3 -> TA : arrival time
114C IR4 -> AREA : element area
115C IR5 -> COSG : direction cosine
116C IR6 -> DIST : distance charge
117C IR7 -> MFLE : fluide mass matrix (inverse) nel < nelmax
118C IR7 -> MFLE : C**t B + B**t C nel >= nelmax
119C IR8 -> ACCF : acceleration point fluide
120C IR9 -> PS : scattered pressure
121C IR10 -> PTI : incident pressure time integral
122C IR11 -> CMAT : Matrice C (nel >= nelmax)
123C-----------------------------------------------------------------------------------
124 ii1 = 1
125 ii2 = 1
126 ii3 = 1
127 ii4 = 1
128 ii5 = 1
129 ii6 = 1
130 ii7 = 1
131 ii8 = 1
132 ii9 = 1
133 ii10= 1
134 ipint=0
135 IF ((tt>=tanim .AND. tt<=tanim_stop).OR.
136 . manim==4 .OR.manim==5 .OR.manim==6 .OR.manim==7.OR.
137 . manim==12.OR.manim==13.OR.manim==14.OR.manim==15)
138 . ipint=1
139 iadi=0
140 iadr=0
141 DO i=1,nflow
142 ityp=iflow(iadi+2)
143 nno=iflow(iadi+5)
144 nel=iflow(iadi+6)
145 ii1=iadi+1
146 ii2=ii1+niflow
147 ii3=ii2+nno
148 ir1=iadr+1
149 ir2=ir1+nrflow
150 IF (ityp==1) THEN
151 ninout=iflow(iadi+4)
152 nnn=iflow(iadi+7)
153 ii4=ii3+3*nel
154 ii5=ii4+ninout*niioflow
155 ii6=ii5+nnn
156 IF (nspmd > 1) THEN
157 ii7=ii6+nel
158 ii8=ii7+nno
159 ii9=ii8+nno
160 ii10=ii9+nno
161 ii11=ii10+nno
162 ii12=ii11+nnn
163 ii13=ii12+nnn
164 ii14=ii13+nel
165 ELSE
166 ii7=ii6+nel
167 ii8=ii7
168 ii9=ii8
169 ii10=ii9+nno
170 ii11=ii10
171 ii12=ii11+nnn
172 ii13=ii12
173 ii14=ii13
174 ENDIF
175 ir3=ir2+nno+nnn
176 ir4=ir3+nno+nnn
177 ir5=ir4+3*(nno+nnn)
178
179 iadip=iflow(iadi+10)
180 iadh=iflow(iadi+11)
181 iadg=iflow(iadi+20)
182
183 CALL incpflow(
184 . nno, nel, ninout, nnn, iflow(ii1),
185 . iflow(ii2), iflow(ii3), iflow(ii4), iflow(ii5), iflow(ii7),
186 . iflow(ii8), iflow(ii9), rflow(ir1), rflow(ir2), rflow(ir3),
187 . rflow(ir4), rflow(ir5), x, v, a,
188 . npc, tf , nsensor , sensor_tab ,
189 . iflow(ii10), iflow(ii6), iflow(ii13), iflow(ii14), wiflow(iadip),
190 . wrflow(iadh),wrflow(iadg),iflow(ii11), iflow(ii12), ipint,
191 . python ,wfext)
192
193 ELSEIF(ityp == 3) THEN
194 jform = iflow(iadi+4)
195 freesurf = iflow(iadi+25)
196 IF(jform==1) THEN
197 ii4=ii3+3*nel
198 ii5=ii4+nno
199 ii6=ii5
200 ndim=3
201 ELSEIF(jform==2) THEN
202 ii4=ii3+5*nel
203 ii5=ii4+nno
204 ii6=ii5+nbgauge
205 ndim=5
206 ENDIF
207
208 ir3 = ir2+nel*3
209 ir4 = ir3+nel*freesurf
210 ir5 = ir4+nel
211 ir6 = ir5+nel*freesurf
212 ir7 = ir6+nel*freesurf
213 ir8 = ir7+nel*nel
214 ir9 = ir8+nel
215 ir10= ir9+nel
216 ir11= ir10+nel
217
218 IF(nspmd == 1) THEN
219 ii7=ii6
220 CALL daasolv(ndim, nno, nel,
221 . iflow(ii1), iflow(ii2), iflow(ii3), iflow(ii5),
222 . rflow(ir1), rflow(ir2), rflow(ir3), rflow(ir4), rflow(ir5), rflow(ir6),
223 . rflow(ir7), rflow(ir8), rflow(ir9), rflow(ir10),x, v, a, npc, tf,
224 . nbgauge, lgauge, gauge, nsensor, sensor_tab, igrv, agrv,
225 . rflow(ir11),iflow(ii7), nfunct, python, wfext)
226 ELSE
227 ii7=ii6+nno
228 ii8=ii7+nel
229 ii9=ii8+nel
230 nel_loc =iflow(iadi+20)
231 iadip =iflow(iadi+10)
232 iadh =iflow(iadi+11)
233 CALL daasolvp(ndim, nno, nel, nel_loc,
234 . iflow(ii1), iflow(ii2), iflow(ii3), iflow(ii4), iflow(ii5), iflow(ii6),
235 . rflow(ir1), rflow(ir2), rflow(ir3), rflow(ir4), rflow(ir5), rflow(ir6),
236 . rflow(ir7), rflow(ir8), rflow(ir9), rflow(ir10),x, v, a, npc, tf,
237 . nbgauge, lgauge, gauge, nsensor, sensor_tab, igrv, agrv,
238 . rflow(ir11),wiflow(iadip), wrflow(iadh), iflow(ii8), iflow(ii9),
239 . nfunct, python, wfext)
240 ENDIF
241 ENDIF
242 iadr=iadr+iflow(iadi+15)
243 iadi=iadi+iflow(iadi+14)
244 ENDDO
245
246 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine daasolv(ndim, nno, nel, iflow, ibuf, elem, shell_ga, rflow, normal, ta, areaf, cosg, dist, mfle, accf, pm, pti, x, v, a, npc, tf, nbgauge, lgauge, gauge, nsensor, sensor_tab, igrv, agrv, cbem, ipiv, nfunct, python, wfext)
Definition daasolv.F:41
subroutine daasolvp(ndim, nno, nel, nel_loc, iflow, ibuf, elem, ibufl, shell_ga, cnp, rflow, normal, ta, areaf, cosg, dist, mfle, accf, pm, pti, x, v, a, npc, tf, nbgauge, lgauge, gauge, nsensor, sensor_tab, igrv, agrv, cbem, ipiv_l, mfle_l, ibufelr, ibufelc, nfunct, python, wfext)
Definition daasolvp.F:42
subroutine incpflow(nno, nel, ninout, nni, iflow, ibuf, elem, iinout, ibufi, ibufr, ibufc, ibufl, rflow, phi, pres, u, rinout, x, v, a, npc, tf, nsensor, sensor_tab, cnp, itagel, ibufelr, ibufelc, ipiv, hbem, gbem, ibufil, cnpi, ipint, python, wfext)
Definition incpflow.F:46