81 TYPE(t_region
),
POINTER :: pregion
87 CHARACTER(CHRLEN) :: rcsidentstring
88 INTEGER :: indcp,indmol,ivg
89 REAL(RFREAL) :: bg2,bl2,bp,bt,bv2,cg2,cl2,cv2,cp,cvg,cvl,cvm,cvv,eo,
g,gc, &
90 ir,mw,p,po,
r,reo,rg,rgas,rl,ro,ru,rv,rvap,rw,ryg,ryl,ryv, &
91 to,u,
v,vfg,vfl,vfv,vm2,w
92 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pdv,pgv
94 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcvspec
97 TYPE(t_grid),
POINTER :: pgrid
103 rcsidentstring =
'$RCSfile: RFLU_ComputeVertexVariables.F90,v $ $Revision: 1.11 $'
105 global => pregion%global
108 'RFLU_ComputeVertexVariables.F90')
110 IF ( global%verbLevel > verbose_none )
THEN
111 WRITE(stdout,
'(A,1X,A)') solver_name,
'Computing vertex variables...'
118 pgrid => pregion%grid
120 pcv => pregion%mixt%cvVert
121 pdv => pregion%mixt%dvVert
122 pgv => pregion%mixt%gvVert
125 pcvspec => pregion%spec%cvVert
128 indcp = pregion%mixtInput%indCp
129 indmol = pregion%mixtInput%indMol
135 SELECT CASE ( pregion%mixtInput%fluidModel )
141 CASE ( fluid_model_incomp )
147 CASE ( fluid_model_comp )
148 IF ( pregion%mixt%cvState /= cv_mixt_state_cons )
THEN
149 CALL
errorstop(global,err_cv_state_invalid,__line__)
152 SELECT CASE ( pregion%mixtInput%gasModel )
158 CASE ( gas_model_tcperf, &
160 gas_model_mixt_tcperf, &
161 gas_model_mixt_tperf, &
162 gas_model_mixt_pseudo )
163 DO ivg = 1,pgrid%nVertTot
164 r = pcv(cv_mixt_dens,ivg)
165 ru = pcv(cv_mixt_xmom,ivg)
166 rv = pcv(cv_mixt_ymom,ivg)
167 rw = pcv(cv_mixt_zmom,ivg)
168 reo = pcv(cv_mixt_ener,ivg)
175 vm2 = u*u +
v*
v + w*w
177 cp = pgv(gv_mixt_cp ,indcp *ivg)
178 mw = pgv(gv_mixt_mol,indmol*ivg)
185 pdv(dv_mixt_pres,ivg) = p
194 CASE ( gas_model_mixt_gasliq )
196 IF ( pregion%mixt%cvState /= cv_mixt_state_cons )
THEN
197 CALL
errorstop(global,err_cv_state_invalid,__line__)
200 ro = global%refDensityLiq
201 po = global%refPressLiq
202 to = global%refTempLiq
203 bp = global%refBetaPLiq
204 bt = global%refBetaTLiq
205 cvl = global%refCvLiq
207 rgas =
mixtperf_r_m(pregion%specInput%specType(1)%pMaterial%molw)
211 rvap =
mixtperf_r_m(pregion%specInput%specType(2)%pMaterial%molw)
215 DO ivg = 1,pgrid%nVertTot
216 r = pcv(cv_mixt_dens,ivg)
217 ru = pcv(cv_mixt_xmom,ivg)
218 rv = pcv(cv_mixt_ymom,ivg)
219 rw = pcv(cv_mixt_zmom,ivg)
220 reo = pcv(cv_mixt_ener,ivg)
227 vm2 = u*u +
v*
v + w*w
233 cvm = (ryl*cvl + ryv*cvv + ryg*cvg)/
r
241 pdv(dv_mixt_pres,ivg) =
mixtgasliq_p(ryl,ryv,ryg,cl2,cv2,cg2,
r,ro, &
243 pdv(dv_mixt_temp,ivg))
245 pdv(dv_mixt_temp,ivg),to)
246 rv =
mixtperf_d_prt(pdv(dv_mixt_pres,ivg),rvap,pdv(dv_mixt_temp,ivg))
247 rg =
mixtperf_d_prt(pdv(dv_mixt_pres,ivg),rgas,pdv(dv_mixt_temp,ivg))
251 vfl = 1.0_rfreal - vfg - vfv
257 pdv(dv_mixt_soun,ivg) =
mixtgasliq_c(cvm,
r,pdv(dv_mixt_pres,ivg), &
258 rl,rv,rg,vfl,vfv,vfg,cl2,cv2, &
262 CALL
errorstop(global,err_reached_default,__line__)
265 CALL
errorstop(global,err_reached_default,__line__)
273 CALL
errorstop(global,err_reached_default,__line__)
280 IF ( global%verbLevel > verbose_none )
THEN
281 WRITE(stdout,
'(A,1X,A)') solver_name,
'Computing vertex variables done.'
real(rfreal) function mixtperf_p_deogvm2(D, Eo, G, Vm2)
real(rfreal) function mixtperf_r_m(M)
subroutine rflu_computevertexvariables(pRegion)
real(rfreal) function mixtperf_c_dgp(D, G, P)
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)
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to and or **sell copies of the and to permit persons to whom the **Software is furnished to do subject to the following this list of conditions and the following disclaimers ****Redistributions in binary form must reproduce the above **copyright this list of conditions and the following **disclaimers in the documentation and or other materials **provided with the distribution ****Neither the names of the Center for Simulation of Advanced the University of nor the names of its **contributors may be used to endorse or promote products derived **from this Software without specific prior written permission ****THE SOFTWARE IS PROVIDED AS WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **ARISING OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE v
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)