84 INTEGER,
INTENT(IN) :: icgbeg,icgend
85 TYPE(t_region
),
POINTER :: pregion
91 CHARACTER(CHRLEN) :: rcsidentstring
92 INTEGER :: icg,indcp,indmol
93 REAL(RFREAL) :: eo,
g,gc,ir,
r,rg,
term,vm2
94 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pdv,pgv
99 REAL(RFREAL) :: bg2,bl2,bp,bt,bv2,cg2,cl2,cpg,cpm,cv2,cvg,cvl,cvm,cvv, &
100 gcg,gcm,gcv,gm,immg,mmg,mmm,phip,po,rl,ro,rv,ryg,ryi,ryl, &
101 ryv,to,vfg,vfl,vfv,yg
102 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcvspec
110 rcsidentstring =
'$RCSfile: RFLU_SetDependentVars.F90,v $ $Revision: 1.11 $'
112 global => pregion%global
115 'RFLU_SetDependentVars.F90')
121 pcv => pregion%mixt%cv
122 pdv => pregion%mixt%dv
123 pgv => pregion%mixt%gv
126 pcvspec => pregion%spec%cv
129 indcp = pregion%mixtInput%indCp
130 indmol = pregion%mixtInput%indMol
136 SELECT CASE ( pregion%mixtInput%fluidModel )
142 CASE ( fluid_model_incomp )
148 CASE ( fluid_model_comp )
149 SELECT CASE ( pregion%mixtInput%gasModel )
155 CASE ( gas_model_tcperf )
156 IF ( pregion%mixt%cvState /= cv_mixt_state_cons )
THEN
157 CALL
errorstop(global,err_cv_state_invalid,__line__)
160 DO icg = icgbeg,icgend
164 r = pcv(cv_mixt_dens,icg)
166 eo = ir*pcv(cv_mixt_ener,icg)
168 vm2 = ir*ir*(pcv(cv_mixt_xmom,icg)*pcv(cv_mixt_xmom,icg) + &
169 pcv(cv_mixt_ymom,icg)*pcv(cv_mixt_ymom,icg) + &
170 pcv(cv_mixt_zmom,icg)*pcv(cv_mixt_zmom,icg))
175 pdv(dv_mixt_temp,icg))
182 CASE ( gas_model_mixt_tcperf )
183 IF ( pregion%mixt%cvState /= cv_mixt_state_cons )
THEN
184 CALL
errorstop(global,err_cv_state_invalid,__line__)
187 DO icg = icgbeg,icgend
191 r = pcv(cv_mixt_dens,icg)
193 eo = ir*pcv(cv_mixt_ener,icg)
195 vm2 = ir*ir*(pcv(cv_mixt_xmom,icg)*pcv(cv_mixt_xmom,icg) + &
196 pcv(cv_mixt_ymom,icg)*pcv(cv_mixt_ymom,icg) + &
197 pcv(cv_mixt_zmom,icg)*pcv(cv_mixt_zmom,icg))
202 pdv(dv_mixt_temp,icg))
209 CASE ( gas_model_mixt_pseudo )
211 IF ( pregion%mixt%cvState /= cv_mixt_state_cons )
THEN
212 CALL
errorstop(global,err_cv_state_invalid,__line__)
215 DO icg = icgbeg,icgend
216 mmm = pgv(gv_mixt_mol,icg)
217 cpm = pgv(gv_mixt_cp ,icg)
221 r = pcv(cv_mixt_dens,icg)
223 eo = ir*pcv(cv_mixt_ener,icg)
229 DO ispec = 1,pregion%specInput%nSpecies
230 pspectype => pregion%specInput%specType(ispec)
232 ryi = pcvspec(ispec,icg)
234 IF ( pspectype%discreteFlag .EQV. .true. )
THEN
235 phip = phip + ryi/pspectype%pMaterial%dens
237 cpg = cpg + ir*ryi*pspectype%pMaterial%spht
244 vm2 = ir*ir*(pcv(cv_mixt_xmom,icg)*pcv(cv_mixt_xmom,icg) + &
245 pcv(cv_mixt_ymom,icg)*pcv(cv_mixt_ymom,icg) + &
246 pcv(cv_mixt_zmom,icg)*pcv(cv_mixt_zmom,icg))
249 pdv(dv_mixt_pres,icg) = cpm/cpg*
term/(1.0_rfreal-phip)
252 pdv(dv_mixt_temp,icg) =
term*(1.0_rfreal-phip)
255 pdv(dv_mixt_soun,icg) =
term/(1.0_rfreal-phip)
258 CALL
errorstop(global,err_reached_default,__line__)
265 CASE ( gas_model_mixt_gasliq )
267 IF ( pregion%mixt%cvState /= cv_mixt_state_cons )
THEN
268 CALL
errorstop(global,err_cv_state_invalid,__line__)
271 ro = global%refDensityLiq
272 po = global%refPressLiq
273 to = global%refTempLiq
274 bp = global%refBetaPLiq
275 bt = global%refBetaTLiq
276 cvl = global%refCvLiq
278 gcg =
mixtperf_r_m(pregion%specInput%specType(1)%pMaterial%molw)
282 gcv =
mixtperf_r_m(pregion%specInput%specType(2)%pMaterial%molw)
286 DO icg = icgbeg,icgend
287 r = pcv(cv_mixt_dens,icg)
289 eo = ir*pcv(cv_mixt_ener,icg)
291 ryg =
r*pcvspec(1,icg)
292 ryv =
r*pcvspec(2,icg)
295 vm2 = ir*ir*(pcv(cv_mixt_xmom,icg)*pcv(cv_mixt_xmom,icg) + &
296 pcv(cv_mixt_ymom,icg)*pcv(cv_mixt_ymom,icg) + &
297 pcv(cv_mixt_zmom,icg)*pcv(cv_mixt_zmom,icg))
298 cvm = (ryl*cvl + ryv*cvv + ryg*cvg)/
r
305 pdv(dv_mixt_pres,icg) =
mixtgasliq_p(ryl,ryv,ryg,cl2,cv2,cg2,
r, &
307 pdv(dv_mixt_temp,icg))
310 pdv(dv_mixt_temp,icg),to)
312 pdv(dv_mixt_temp,icg))
314 pdv(dv_mixt_temp,icg))
324 pdv(dv_mixt_soun,icg) =
mixtgasliq_c(cvm,
r,pdv(dv_mixt_pres,icg), &
325 rl,rv,rg,vfl,vfv,vfg,cl2, &
329 CALL
errorstop(global,err_reached_default,__line__)
337 CALL
errorstop(global,err_reached_default,__line__)
345 CALL
errorstop(global,err_reached_default,__line__)
real(rfreal) function mixtperf_p_deogvm2(D, Eo, G, Vm2)
real(rfreal) function mixtperf_r_m(M)
subroutine rflu_setdependentvars(pRegion, icgBeg, icgEnd)
subroutine registerfunction(global, funName, fileName)
real(rfreal) function mixtperf_d_prt(P, R, T)
real(rfreal) function mixtgasliq_p(DYl, DYv, DYg, Cl2, Cv2, Cg2, D, Dz, Po, To, Bp, Bt, T)
real(rfreal) function mixtperf_c2_grt(G, R, T)
real(rfreal) function mixtliq_c2_bp(Bp)
real(rfreal) function mixtperf_t_dpr(D, P, R)
real(rfreal) function mixtliq_d_dobpppobttto(Dz, Bp, Bt, P, Po, T, To)
real(rfreal) function mixtperf_c_grt(G, R, T)
real(rfreal) function mixtgasliq_c(Cvm, D, P, Dl, Dv, Dg, VFl, VFv, VFg, Cl2, Cv2, Cg2, Bl2, Bv2, Bg2)
subroutine errorstop(global, errorCode, errorLine, addMessage)
real(rfreal) function mixtperf_t_cveovm2(Cv, Eo, Vm2)
subroutine deregisterfunction(global)
real(rfreal) function mixtperf_g_cpr(Cp, R)
real(rfreal) function mixtperf_cv_cpr(Cp, R)