103 INTEGER,
INTENT(IN) :: cvstatefuture
104 TYPE(t_region
),
POINTER :: pregion
110 INTEGER :: icg,indmol
111 REAL(RFREAL) :: gc,ir,mw,p,
r
112 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pdv,pgv
113 TYPE(t_grid),
POINTER :: pgrid
120 global => pregion%global
123 'RFLU_ModConvertCv.F90')
126 CALL fprofiler_begins(
"RFLU::ConvertCvCons2Prim")
133 pgrid => pregion%grid
134 pcv => pregion%mixt%cv
135 pdv => pregion%mixt%dv
136 pgv => pregion%mixt%gv
138 indmol = pregion%mixtInput%indMol
144 SELECT CASE ( pregion%mixt%cvState )
150 CASE ( cv_mixt_state_cons )
151 SELECT CASE ( cvstatefuture )
157 CASE ( cv_mixt_state_duvwp )
158 pregion%mixt%cvState = cv_mixt_state_duvwp
160 DO icg = 1,pgrid%nCellsTot
161 ir = 1.0_rfreal/pcv(cv_mixt_dens,icg)
163 pcv(cv_mixt_xvel,icg) = ir*pcv(cv_mixt_xmom,icg)
164 pcv(cv_mixt_yvel,icg) = ir*pcv(cv_mixt_ymom,icg)
165 pcv(cv_mixt_zvel,icg) = ir*pcv(cv_mixt_zmom,icg)
166 pcv(cv_mixt_pres,icg) = pdv(dv_mixt_pres,icg)
173 CASE (cv_mixt_state_duvwt)
174 pregion%mixt%cvState = cv_mixt_state_duvwt
176 SELECT CASE ( pregion%mixtInput%fluidModel )
180 CASE ( fluid_model_comp )
181 SELECT CASE ( pregion%mixtInput%gasModel )
185 CASE ( gas_model_tcperf, &
186 gas_model_mixt_tcperf, &
187 gas_model_mixt_pseudo )
188 DO icg = 1,pgrid%nCellsTot
189 r = pcv(cv_mixt_dens,icg)
190 p = pdv(dv_mixt_pres,icg)
193 pcv(cv_mixt_xvel,icg) = ir*pcv(cv_mixt_xmom,icg)
194 pcv(cv_mixt_yvel,icg) = ir*pcv(cv_mixt_ymom,icg)
195 pcv(cv_mixt_zvel,icg) = ir*pcv(cv_mixt_zmom,icg)
197 mw = pgv(gv_mixt_mol,indmol*icg)
205 CASE ( gas_model_mixt_gasliq )
206 DO icg = 1,pgrid%nCellsTot
207 ir = 1.0_rfreal/pcv(cv_mixt_dens,icg)
209 pcv(cv_mixt_xvel,icg) = ir*pcv(cv_mixt_xmom,icg)
210 pcv(cv_mixt_yvel,icg) = ir*pcv(cv_mixt_ymom,icg)
211 pcv(cv_mixt_zvel,icg) = ir*pcv(cv_mixt_zmom,icg)
213 pcv(cv_mixt_temp,icg) = pdv(dv_mixt_temp,icg)
216 CALL
errorstop(global,err_reached_default,__line__)
222 CALL
errorstop(global,err_reached_default,__line__)
230 CALL
errorstop(global,err_reached_default,__line__)
238 CALL
errorstop(global,err_reached_default,__line__)
246 CALL fprofiler_ends(
"RFLU::ConvertCvCons2Prim")
291 INTEGER,
INTENT(IN) :: cvstatefuture
292 TYPE(t_region
),
POINTER :: pregion
298 INTEGER :: icg,indcp,indmol
299 REAL(RFREAL) :: cp,cvm,cvg,cvl,cvv,
g,gc,mw,p,
r,rg,rv,ryg,ryl,ryv,t,u,
v, &
301 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pdv,pgv
303 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcvspec
305 TYPE(t_grid),
POINTER :: pgrid
312 global => pregion%global
315 'RFLU_ModConvertCv.F90')
318 CALL fprofiler_begins(
"RFLU::ConvertCvPrim2Cons")
325 pgrid => pregion%grid
326 pcv => pregion%mixt%cv
327 pdv => pregion%mixt%dv
328 pgv => pregion%mixt%gv
331 pcvspec => pregion%spec%cv
334 indcp = pregion%mixtInput%indCp
335 indmol = pregion%mixtInput%indMol
341 IF ( pregion%mixt%cvState == cv_mixt_state_duvwp .OR. &
342 pregion%mixt%cvState == cv_mixt_state_duvwt )
THEN
348 SELECT CASE ( cvstatefuture )
349 CASE ( cv_mixt_state_cons )
350 pregion%mixt%cvState = cv_mixt_state_cons
352 SELECT CASE ( pregion%mixtInput%gasModel )
358 CASE ( gas_model_tcperf, &
359 gas_model_mixt_tcperf, &
360 gas_model_mixt_pseudo )
361 DO icg = 1,pgrid%nCellsTot
362 r = pcv(cv_mixt_dens,icg)
363 u = pcv(cv_mixt_xvel,icg)
364 v = pcv(cv_mixt_yvel,icg)
365 w = pcv(cv_mixt_zvel,icg)
366 p = pdv(dv_mixt_pres,icg)
368 pcv(cv_mixt_xmom,icg) =
r*u
369 pcv(cv_mixt_ymom,icg) =
r*
v
370 pcv(cv_mixt_zmom,icg) =
r*w
372 cp = pgv(gv_mixt_cp,indcp*icg)
373 mw = pgv(gv_mixt_mol,indmol*icg)
384 CASE ( gas_model_mixt_gasliq )
394 cvl = global%refCvLiq
396 DO icg = 1,pgrid%nCellsTot
397 r = pcv(cv_mixt_dens,icg)
398 u = pcv(cv_mixt_xvel,icg)
399 v = pcv(cv_mixt_yvel,icg)
400 w = pcv(cv_mixt_zvel,icg)
401 t = pdv(dv_mixt_temp,icg)
403 pcv(cv_mixt_xmom,icg) =
r*u
404 pcv(cv_mixt_ymom,icg) =
r*
v
405 pcv(cv_mixt_zmom,icg) =
r*w
411 cvm = (ryl*cvl + ryg*cvg + ryv*cvv)/
r
412 vm2 = u*u +
v*
v + w*w
417 CALL
errorstop(global,err_gasmodel_invalid,__line__, &
418 'Can only be used with species module.')
426 CALL
errorstop(global,err_reached_default,__line__)
430 CALL
errorstop(global,err_reached_default,__line__)
438 CALL
errorstop(global,err_reached_default,__line__)
446 CALL fprofiler_ends(
"RFLU::ConvertCvPrim2Cons")
483 INTEGER,
INTENT(INOUT) :: cvscalstatecurrent
484 REAL(RFREAL),
DIMENSION(:,:) :: cvscal
485 TYPE(t_region
),
POINTER :: pregion
491 INTEGER :: icg,iscal,nscal
493 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv
494 TYPE(t_grid),
POINTER :: pgrid
501 global => pregion%global
504 'RFLU_ModConvertCv.F90')
510 pgrid => pregion%grid
511 pcv => pregion%mixt%cv
513 nscal =
SIZE(cvscal,1)
519 SELECT CASE ( cvscalstatecurrent )
525 CASE ( cv_mixt_state_cons )
526 cvscalstatecurrent = cv_mixt_state_prim
528 DO icg = 1,pgrid%nCellsTot
529 ir = 1.0_rfreal/pcv(cv_mixt_dens,icg)
532 cvscal(iscal,icg) = ir*cvscal(iscal,icg)
541 CALL
errorstop(global,err_reached_default,__line__)
582 INTEGER,
INTENT(INOUT) :: cvscalstatecurrent
583 REAL(RFREAL),
DIMENSION(:,:) :: cvscal
584 TYPE(t_region
),
POINTER :: pregion
590 INTEGER :: icg,iscal,nscal
592 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv
593 TYPE(t_grid),
POINTER :: pgrid
600 global => pregion%global
603 'RFLU_ModConvertCv.F90')
609 pgrid => pregion%grid
610 pcv => pregion%mixt%cv
612 nscal =
SIZE(cvscal,1)
618 SELECT CASE ( cvscalstatecurrent )
624 CASE ( cv_mixt_state_prim )
625 cvscalstatecurrent = cv_mixt_state_cons
627 DO icg = 1,pgrid%nCellsTot
628 r = pcv(cv_mixt_dens,icg)
631 cvscal(iscal,icg) =
r*cvscal(iscal,icg)
640 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
subroutine, public rflu_convertcvcons2prim(pRegion, cvStateFuture)
subroutine, public rflu_convertcvprim2cons(pRegion, cvStateFuture)
subroutine, public rflu_scalarconvertcvprim2cons(pRegion, cvScal, cvScalStateCurrent)
real(rfreal) function mixtperf_t_dpr(D, P, R)
real(rfreal) function mixtgasliq_eo_cvmtvm2(Cvm, T, Vm2)
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_scalarconvertcvcons2prim(pRegion, cvScal, cvScalStateCurrent)