56 TYPE(t_region
),
TARGET :: pregion
57 INTEGER,
INTENT(IN) :: cvstatefuture
63 CHARACTER(CHRLEN) :: rcsidentstring
64 INTEGER ::
ic,indcp,indmol
65 REAL(RFREAL) :: cp,
g,mol,p,
r,rgas,u,
v,w
66 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pdv,pgv
67 TYPE(t_grid),
POINTER :: pgrid
74 rcsidentstring =
'$RCSfile: TURB_fluCv2Cons.F90,v $ $Revision: 1.4 $'
76 global => pregion%global
79 'TURB_fluCv2Cons.F90')
86 pcv => pregion%mixt%cv
87 pdv => pregion%mixt%dv
88 pgv => pregion%mixt%gv
90 indcp = pregion%mixtInput%indCp
91 indmol = pregion%mixtInput%indMol
97 IF ( pregion%mixt%cvState == cv_mixt_state_duvwp .OR. &
98 pregion%mixt%cvState == cv_mixt_state_duvwt )
THEN
104 SELECT CASE (cvstatefuture)
105 CASE (cv_mixt_state_cons)
106 pregion%mixt%cvState = cv_mixt_state_cons
108 SELECT CASE (pregion%mixtInput%gasModel)
112 CASE (gas_model_tcperf)
113 DO ic = 1,pgrid%nCellsTot
114 r = pcv(cv_mixt_dens,
ic)
115 u = pcv(cv_mixt_xvel,
ic)
116 v = pcv(cv_mixt_yvel,
ic)
117 w = pcv(cv_mixt_zvel,
ic)
118 p = pdv(dv_mixt_pres,
ic)
120 pcv(cv_mixt_xmom,
ic) =
r*u
121 pcv(cv_mixt_ymom,
ic) =
r*
v
122 pcv(cv_mixt_zmom,
ic) =
r*w
124 cp = pgv(gv_mixt_cp,indcp*
ic)
125 mol = pgv(gv_mixt_mol,indmol*
ic)
135 CALL
errorstop(global,err_reached_default,__line__)
139 CALL
errorstop(global,err_reached_default,__line__)
147 CALL
errorstop(global,err_reached_default,__line__)
subroutine turb_flucv2cons(pRegion, cvStateFuture)
real(rfreal) function mixtperf_r_m(M)
subroutine registerfunction(global, funName, fileName)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com 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 **********************************************************************INTERFACE SUBROUTINE ic
*********************************************************************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_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)