CalculiX  2.13
A Free Software Three-Dimensional Structural Finite Element Program
two_phase_flow.f File Reference

Go to the source code of this file.

Functions/Subroutines

subroutine two_phase_flow (Tt1, pt1, T1, pt2, xflow_air, xflow_oil, nelem, lakon, kon, ipkon, ielprop, prop, v, dvi_air, cp, r, k_oil, phi, lambda, nshcon, nrhcon, shcon, rhcon, ntmat_, mi, iaxial)
 

Function/Subroutine Documentation

◆ two_phase_flow()

subroutine two_phase_flow ( real*8, intent(in)  Tt1,
real*8, intent(in)  pt1,
real*8, intent(in)  T1,
real*8, intent(in)  pt2,
real*8, intent(inout)  xflow_air,
real*8, intent(in)  xflow_oil,
integer, intent(in)  nelem,
character*8, dimension(*), intent(in)  lakon,
integer, dimension(*), intent(in)  kon,
integer, dimension(*), intent(in)  ipkon,
integer, dimension(*), intent(in)  ielprop,
real*8, dimension(*), intent(in)  prop,
real*8, dimension(0:mi(2),*), intent(in)  v,
real*8, intent(in)  dvi_air,
real*8, intent(in)  cp,
real*8, intent(in)  r,
integer, intent(in)  k_oil,
real*8, intent(inout)  phi,
real*8, intent(inout)  lambda,
integer, dimension(*), intent(in)  nshcon,
integer, dimension(*), intent(in)  nrhcon,
real*8, dimension(0:3,ntmat_,*), intent(in)  shcon,
real*8, dimension(0:1,ntmat_,*), intent(in)  rhcon,
integer, intent(in)  ntmat_,
integer, dimension(*), intent(in)  mi,
integer, intent(in)  iaxial 
)
23 !
24 ! two phase flow correlations
25 !
26 ! author: Yannick Muller
27 !
28  implicit none
29 !
30  character*8 lakon(*)
31 !
32  integer nelem,ielprop(*),index,mi(*),iaxial,
33  & ipkon(*),kon(*),icase,kgas,k_oil,mtlog,ier,nshcon(*),
34  & nrhcon(*),ntmat_,n1,n2,n11
35 !
36  real*8 prop(*),v(0:mi(2),*),kappa,r,a,d,dl,
37  & t1,tt1,pt1,pt2,cp,dvi_air,dvi_oil,
38  & reynolds,lambda,ks,form_fact,f,
39  & l_neg,xflow_air,xflow_oil,a1,a2,
40  & rho_air,rho_oil,nue_air,nue_oil,zeta,reynolds_h,mpg,
41  & xp,xpm2,xpmini,isothermal,dvi_h,zeta_h,auxphi,
42  & rad,theta,phi,phizeta,x,
43  & rho_q,p1,shcon(0:3,ntmat_,*),
44  & rhcon(0:1,ntmat_,*),cp_oil,r_oil
45 !
46  parameter( xpmini=1.e10)
47 !
48 ! this subroutine enables to take in account the existence of
49 ! 2 phase flows (air /oil) in some flow elements.
50 !
51 ! lambda: friction coefficient solely due to air
52 ! phi: correction due to the presence of oil
53 ! (lambda_corrected=lambda*phi)
54 !
55 ! the 2 following tables are used in Lockhart Martinelli Method.
56 ! See table p.44
57 !
58  real*8 tx(17),tf(17)
59  data tx
60  & /0.01d0,0.02d0,0.04d0,0.07d0,
61  & 0.10d0,0.20d0,0.40d0,0.70d0,
62  & 1.00d0,2.00d0,4.00d0,7.00d0,
63  & 10.0d0,20.0d0,40.0d0,70.0d0,
64  & 100.d0/
65 !
66  data tf
67  & /1.28d0,1.37d0,1.54d0,1.71d0,
68  & 1.85d0,2.23d0,2.83d0,3.53d0,
69  & 4.20d0,6.20d0,9.50d0,13.7d0,
70  & 17.5d0,29.5d0,51.5d0,82.0d0,
71  & 111.d0/
72 !
73  data n1 /1/
74  data n2 /2/
75  data n11 /11/
76 !
77  intent(in) tt1,pt1,t1,pt2,
78  & xflow_oil,nelem,lakon,kon,ipkon,ielprop,prop,v,
79  & dvi_air,cp,r,k_oil,nshcon,nrhcon,shcon,
80  & rhcon,ntmat_,mi,iaxial
81 !
82  intent(inout) lambda,phi,xflow_air
83 !
84  index=ielprop(nelem)
85 !
86  if(lakon(nelem)(2:5).eq.'GAPF') then
87  a=prop(index+1)
88  d=prop(index+2)
89  dl=prop(index+3)
90  ks=prop(index+4)
91  form_fact=prop(index+5)
92  endif
93 !
94  if(xflow_oil.eq.0.d0) then
95  write(*,*) '*WARNING:in two_phase_flow'
96  write(*,*) 'massflow oil for element',nelem,'in null'
97  write(*,*) 'Calculation proceeds without oil correction'
98  phi=1.d0
99  endif
100 !
101 
102  xflow_air=dabs(xflow_air)
103  kappa=cp/(cp-r)
104 !
105 ! First case:
106 ! the element is a restrictor of type
107 ! THICK-WALLED ORIFICE IN LARGE WALL (L/DH > 0.015)
108 ! I.E. IDL'CHIK (SECTION IV PAGE 144)!
109 ! and
110 ! Second case:
111 ! the element is a restrictor of type
112 ! SMOOTH BENDS B.H.R.A HANDBOOK (Miller)
113 !
114 ! Two phase flow correlations are taken from:
115 ! H.Zimmermann, A.Kammerer, R.Fischer and D. Rebhan
116 ! "Two phase flow correlations in Air/Oil systems of
117 ! Aero Engines."
118 ! ASME 91-GT-54
119 !
120  if((lakon(nelem)(2:7).eq.'RELOID').or.
121  & (lakon(nelem)(2:7).eq.'REBEMI')) then
122 !
123  icase=0
124 !
125  a1=prop(index+1)
126  a2=prop(index+2)
127  call ts_calc(xflow_air,tt1,pt1,kappa,r,a1,t1,icase)
128 !
129  d=dsqrt(a1*4/(4.d0*datan(1.d0)))
130 !
131 ! calculating the dynamic viscosity, the kinematic viscosity and
132 ! the density of air
133 !
134  kgas=0
135 !
136  p1=pt1*(t1/tt1)**(kappa/kappa-1)
137  rho_air=p1/(r*t1)
138  nue_air=dvi_air/rho_air
139 !
140 ! calculating the dynamic viscosity, the kinematic viscosity and
141 ! the density of oil
142 !
143  call materialdata_tg(k_oil,ntmat_,t1,shcon,nshcon,cp_oil,r_oil,
144  & dvi_oil,rhcon,nrhcon,rho_oil)
145 !
146  if(xflow_oil.eq.0.d0) then
147 !
148 ! pure air
149  call zeta_calc(nelem,prop,ielprop,lakon,reynolds,zeta,
150  & isothermal,kon,ipkon,r,kappa,v,mi,iaxial)
151  lambda=zeta
152  return
153  else
154 !
155 ! air/oil mixture for orifice or bend
156 ! For Bend see section 4.2.1
157 ! For orifices see 4.2.3
158 !
159  mpg=xflow_air+xflow_oil
160  xp=xflow_air/mpg
161  if(mpg.gt.xflow_air*xpmini) then
162  xpm2=xpmini**2
163  else
164  xpm2=(mpg/xflow_air)**2
165  endif
166 !
167  rho_q=rho_oil/rho_air
168 !
169 ! homogene dynamic viscosity (mass flow rate averaged)
170 !
171  dvi_h=dvi_oil*dvi_air/((dvi_oil-dvi_air)*xp+dvi_air)
172 !
173 ! homogene reynolds number
174 !
175  reynolds_h=mpg*d/(a1*dvi_h)
176 !
177  call zeta_calc(nelem,prop,ielprop,lakon,reynolds_h,zeta_h,
178  & isothermal,kon,ipkon,r,kappa,v,mi,iaxial)
179 !
180 ! orifice in a wall
181 !
182  if(lakon(nelem)(2:7).eq.'RELOID') then
183 
184  auxphi=(1.d0+xp*(rho_q**(1.d0/6.d0)-1.d0))
185  & *(1.d0+xp*(rho_q**(5.d0/6.d0)-1.d0))
186 !
187 ! bend
188 !
189  elseif(lakon(nelem)(2:7).eq.'REBEMI') then
190 !
191 ! radius of the bend
192 !
193  rad=prop(index+4)
194 !
195 ! angle of the bend
196 !
197  theta=prop(index+5)
198 !
199  f=(1.d0+2.2d0*theta/90.d0/(zeta_h*(2.d0+rad/d)))
200  & *xp*(1.d0-xp)+xp**2
201 !
202  auxphi=1.d0+(rho_q-1.d0)*f
203  endif
204 !
205  phi=1/rho_q*auxphi*xpm2
206  phizeta=zeta_h/rho_q*auxphi*xpm2
207  lambda=zeta_h
208 !
209  endif
210 !
211 ! Third case:
212 ! the element is a pipe
213 ! the zeta coefficient is corrected according to
214 ! Lockhart Martinelli Method
215 ! Reference: R.W. Lockhart and R.C. Martinelli
216 ! University of California, BErkeley, California
217 ! "Proposed correlation of data for
218 ! isothermal two-phase two-component
219 ! flow in pipes"
220 ! Chemical Engineering Progress vol.45, N°1
221 !
222  elseif((lakon(nelem)(2:5).eq.'GAPF')
223  & .or.((lakon(nelem)(2:7).ne.'REBEMI')
224  & .and.(lakon(nelem)(2:7)).ne.'RELOID'))then
225 !
226  if(lakon(nelem)(2:6).eq.'GAPFA') then
227  icase=0
228  elseif(lakon(nelem)(2:6).eq.'GAPFI') then
229  icase=1
230  else
231  icase=0
232  endif
233 !
234  if((lakon(nelem)(2:3).eq.'RE').and.
235  & (lakon(nelem)(4:5).ne.'BR')) then
236  a=min(prop(index+1),prop(index+2))
237  endif
238 !
239  call ts_calc(xflow_air,tt1,pt1,kappa,r,a,t1,icase)
240 !
241 ! calculating kinematic viscosity and density for air
242 !
243  p1=pt1*(t1/tt1)**(kappa/kappa-1)
244  rho_air=p1/(r*t1)
245  nue_air=dvi_air/rho_air
246 !
247 ! calculation of the dynamic viscosity for oil
248 !
249  call materialdata_tg(k_oil,ntmat_,t1,shcon,nshcon,cp_oil,r_oil,
250  & dvi_oil,rhcon,nrhcon,rho_oil)
251 !
252  nue_oil=dvi_oil/rho_oil
253 !
254 ! Definition of the two phase flow modulus as defined in table 1
255 !
256  x=dabs(xflow_oil/xflow_air)*(rho_air/rho_oil)**(0.553d0)
257  & *(nue_oil/nue_air)**(0.111d0)
258 !
259  mtlog=17
260 ! Interpolating x in the table
261  call onedint(tx,tf,mtlog,x,phi,n1,n2,n11,ier)
262 !
263  if((lakon(nelem)(2:4).eq.'GAP'))then
264 !
265 ! Computing the friction coefficient
266 !
267  reynolds=dabs(xflow_air)*d/(dvi_air*a)
268 !
269  if(reynolds.lt.100.d0) then
270  reynolds= 100.d0
271  endif
272 !
273  call friction_coefficient(l_neg,d,ks,reynolds,form_fact,
274  & lambda)
275  else
276  lambda=0
277  endif
278  endif
279 !
280  return
subroutine zeta_calc(nelem, prop, ielprop, lakon, reynolds, zeta, isothermal, kon, ipkon, R, kappa, v, mi, iaxial)
Definition: zeta_calc.f:35
#define min(a, b)
Definition: cascade.c:31
subroutine ts_calc(xflow, Tt, Pt, kappa, r, A, Ts, icase)
Definition: ts_calc.f:20
subroutine friction_coefficient(l, d, ks, reynolds, form_fact, lambda)
Definition: friction_coefficient.f:26
subroutine onedint(XE, YE, NE, XA, YA, NA, IART, IEXP, IER)
Definition: onedint.f:67
subroutine materialdata_tg(imat, ntmat_, t1l, shcon, nshcon, sph, r, dvi, rhcon, nrhcon, rho)
Definition: materialdata_tg.f:20
Hosted by OpenAircraft.com, (Michigan UAV, LLC)