67 SUBROUTINE bcondoutflowperf_gl(bcOpt,ro,Po,To,betaP,betaT,cvl,cvv,cvg,Rg,Rv, &
68 pout,sxn,syn,szn,rho,rhou,rhov,rhow,rhoe, &
69 rhogpg,rhovpv,
pin,rhob,rhoub,rhovb,rhowb, &
70 rhoeb,rhogpgb,rhovpvb)
92 REAL(RFREAL),
INTENT(IN) :: betap,betat,cvg,cvl,cvv,
pin,po,pout,rg,rho,rhoe, &
93 rhogpg,rhou,rhov,rhovpv,rhow,ro,rv,sxn,syn,szn,to
94 REAL(RFREAL),
INTENT(OUT) :: rhob,rhoeb,rhogpgb,rhoub,rhovb,rhovpvb,rhowb
100 REAL(RFREAL) :: bg2,bl2,bv2,cg2,cl2,cm,ct2,cv2,cvm,deltp,e,fg,fv,ic2p,ic2pb, &
101 mach,rhg,rhgb,rhl,rhlb,rholpl,rhv,rhvb,rrhoc,t,tb,u,ub,
v,vb, &
102 vel2,vfg,vfgb,vfl,vflb,vfv,vfvb,vnd,w,wb
111 vel2 = (u*u +
v*
v + w*w)
113 rholpl = rho - rhovpv - rhogpg
114 cvm = (rholpl*cvl + rhovpv*cvv + rhogpg*cvg)/rho
133 cm =
mixtgasliq_c(cvm,rho,
pin,rhl,rhv,rhg,vfl,vfv,vfg,cl2,cv2,cg2, &
141 IF ( mach < 1.0_rfreal )
THEN
142 rrhoc = 1.0_rfreal/(rho*cm)
144 ub = u + sxn*deltp*rrhoc
145 vb =
v + syn*deltp*rrhoc
146 wb = w + szn*deltp*rrhoc
148 tb = t - (deltp*
pin)/(rho*rho*cvm*cm*cm)
149 fg = (vfg*(rhg*cg2 - rho*cm*cm +(bg2*
pin)/(rho*cvm)))/(rhg*cg2*rho*cm*cm)
150 fv = (vfv*(rhv*cv2 - rho*cm*cm +(bv2*
pin)/(rho*cvm)))/(rhv*cv2*rho*cm*cm)
152 vfgb = vfg - deltp*fg
153 vfvb = vfv - deltp*fv
154 vflb = 1.0_rfreal - vfgb - vfvb
156 ic2p = vfl/cl2 + vfg/cg2 + vfv/cv2
157 ic2pb = (bl2*vfl)/cl2 + (bg2*vfg)/cg2 + (bv2*vfv)/cv2
159 rhob = rho - (rhv-rhl)*(vfl-vflb) - (rhg-rhl)*(vfg-vfgb) &
160 - deltp*ic2p + ic2pb*(t-tb)
161 rhlb = rhl - deltp/cl2 + (bl2*(t-tb))/cl2
162 rhvb = rhv - deltp/cv2 + (bv2*(t-tb))/cv2
163 rhgb = rhg - deltp/cg2 + (bg2*(t-tb))/cg2
170 vnd = ub*sxn + vb*syn + wb*szn
172 IF ( vnd < 0.0_rfreal )
THEN
173 ub =
sign(1.0_rfreal,u)*
max(abs(ub),abs(u))
174 vb =
sign(1.0_rfreal,
v)*
max(abs(vb),abs(
v))
175 wb =
sign(1.0_rfreal,w)*
max(abs(wb),abs(w))
181 rhoeb = (rhlb*vflb*cvl +rhgb*vfgb*cvg +rhvb*vfvb*cvv)*tb + &
182 0.5_rfreal*rhob*(ub*ub + vb*vb + wb*wb)
static SURF_BEGIN_NAMESPACE double sign(double x)
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
real(rfreal) function mixtperf_d_prt(P, R, 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)
blockLoc pin(const blockLoc &l) const
real(rfreal) function mixtliq_d_dobpppobttto(Dz, Bp, Bt, P, Po, T, To)
real(rfreal) function mixtgasliq_c(Cvm, D, P, Dl, Dv, Dg, VFl, VFv, VFg, Cl2, Cv2, Cg2, Bl2, Bv2, Bg2)
real(rfreal) function mixtperf_t_cveovm2(Cv, Eo, Vm2)
subroutine bcondoutflowperf_gl(bcOpt, ro, Po, To, betaP, betaT, cvl, cvv, cvg, Rg, Rv, pout, sxn, syn, szn, rho, rhou, rhov, rhow, rhoe, rhogpg, rhovpv, pin, rhob, rhoub, rhovb, rhowb, rhoeb, rhogpgb, rhovpvb)