101 INTEGER,
INTENT(IN) :: cvstatefuture
102 TYPE(t_patch),
POINTER :: ppatch
103 TYPE(t_region
),
POINTER :: pregion
109 INTEGER :: icg,ifl,indmol
110 REAL(RFREAL) :: gc,ir,mw,p,
r
111 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pdv,pgv
118 global => pregion%global
121 'RFLU_ModBoundConvertCv.F90')
127 pcv => ppatch%mixt%cv
128 pdv => ppatch%mixt%dv
130 pgv => pregion%mixt%gv
132 indmol = pregion%mixtInput%indMol
138 SELECT CASE ( ppatch%mixt%cvState )
144 CASE ( cv_mixt_state_cons )
145 SELECT CASE ( cvstatefuture )
151 CASE ( cv_mixt_state_duvwp )
152 ppatch%mixt%cvState = cv_mixt_state_duvwp
154 DO ifl = 1,ppatch%nBFaces
155 ir = 1.0_rfreal/pcv(cv_mixt_dens,ifl)
157 pcv(cv_mixt_xvel,ifl) = ir*pcv(cv_mixt_xmom,ifl)
158 pcv(cv_mixt_yvel,ifl) = ir*pcv(cv_mixt_ymom,ifl)
159 pcv(cv_mixt_zvel,ifl) = ir*pcv(cv_mixt_zmom,ifl)
160 pcv(cv_mixt_pres,ifl) = pdv(dv_mixt_pres,ifl)
167 CASE (cv_mixt_state_duvwt)
168 ppatch%mixt%cvState = cv_mixt_state_duvwt
170 SELECT CASE ( pregion%mixtInput%fluidModel )
174 CASE ( fluid_model_comp )
175 SELECT CASE ( pregion%mixtInput%gasModel )
179 CASE ( gas_model_tcperf, &
180 gas_model_mixt_tcperf, &
181 gas_model_mixt_pseudo )
182 DO ifl = 1,ppatch%nBFaces
183 icg = ppatch%bf2c(ifl)
185 r = pcv(cv_mixt_dens,ifl)
186 p = pdv(dv_mixt_pres,ifl)
189 pcv(cv_mixt_xvel,ifl) = ir*pcv(cv_mixt_xmom,ifl)
190 pcv(cv_mixt_yvel,ifl) = ir*pcv(cv_mixt_ymom,ifl)
191 pcv(cv_mixt_zvel,ifl) = ir*pcv(cv_mixt_zmom,ifl)
193 mw = pgv(gv_mixt_mol,indmol*icg)
201 CASE ( gas_model_mixt_gasliq )
202 DO ifl = 1,ppatch%nBFaces
203 icg = ppatch%bf2c(ifl)
205 ir = 1.0_rfreal/pcv(cv_mixt_dens,ifl)
207 pcv(cv_mixt_xvel,ifl) = ir*pcv(cv_mixt_xmom,ifl)
208 pcv(cv_mixt_yvel,ifl) = ir*pcv(cv_mixt_ymom,ifl)
209 pcv(cv_mixt_zvel,ifl) = ir*pcv(cv_mixt_zmom,ifl)
211 pcv(cv_mixt_temp,ifl) = pdv(dv_mixt_temp,ifl)
214 CALL
errorstop(global,err_reached_default,__line__)
220 CALL
errorstop(global,err_reached_default,__line__)
228 CALL
errorstop(global,err_reached_default,__line__)
236 CALL
errorstop(global,err_reached_default,__line__)
288 INTEGER,
INTENT(IN) :: cvstatefuture
289 TYPE(t_patch),
POINTER :: ppatch
290 TYPE(t_region
),
POINTER :: pregion
296 INTEGER :: icg,ifl,indcp,indmol
297 REAL(RFREAL) :: cp,cvm,cvg,cvl,cvv,
g,gc,mw,p,
r,rg,rv,ryg,ryl,ryv,t,u,
v, &
299 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pdv,pgv
306 global => pregion%global
309 'RFLU_ModBoundConvertCv.F90')
315 pcv => ppatch%mixt%cv
316 pdv => ppatch%mixt%dv
318 pgv => pregion%mixt%gv
320 indcp = pregion%mixtInput%indCp
321 indmol = pregion%mixtInput%indMol
327 IF ( ppatch%mixt%cvState == cv_mixt_state_duvwp .OR. &
328 ppatch%mixt%cvState == cv_mixt_state_duvwt )
THEN
334 SELECT CASE ( cvstatefuture )
335 CASE ( cv_mixt_state_cons )
336 ppatch%mixt%cvState = cv_mixt_state_cons
338 SELECT CASE ( pregion%mixtInput%gasModel )
344 CASE ( gas_model_tcperf, &
345 gas_model_mixt_tcperf, &
346 gas_model_mixt_pseudo )
347 DO ifl = 1,ppatch%nBFaces
348 icg = ppatch%bf2c(ifl)
350 r = pcv(cv_mixt_dens,ifl)
351 u = pcv(cv_mixt_xvel,ifl)
352 v = pcv(cv_mixt_yvel,ifl)
353 w = pcv(cv_mixt_zvel,ifl)
354 p = pdv(dv_mixt_pres,ifl)
356 pcv(cv_mixt_xmom,ifl) =
r*u
357 pcv(cv_mixt_ymom,ifl) =
r*
v
358 pcv(cv_mixt_zmom,ifl) =
r*w
360 cp = pgv(gv_mixt_cp,indcp*icg)
361 mw = pgv(gv_mixt_mol,indmol*icg)
372 CASE ( gas_model_mixt_gasliq )
373 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
374 'Can only be used with species module.')
381 CALL
errorstop(global,err_reached_default,__line__)
385 CALL
errorstop(global,err_reached_default,__line__)
393 CALL
errorstop(global,err_reached_default,__line__)
real(rfreal) function mixtperf_r_m(M)
subroutine registerfunction(global, funName, fileName)
*********************************************************************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_t_dpr(D, P, R)
real(rfreal) function mixtgasliq_eo_cvmtvm2(Cvm, T, Vm2)
subroutine, public rflu_bxv_convertcvcons2prim(pRegion, pPatch, cvStateFuture)
real(rfreal) function mixtperf_eo_dgpuvw(D, G, P, U, V, W)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)
real(rfreal) function mixtperf_g_cpr(Cp, R)
real(rfreal) function mixtperf_cv_cpr(Cp, R)
subroutine, public rflu_bxv_convertcvprim2cons(pRegion, pPatch, cvStateFuture)