69 TYPE(t_region
),
POINTER :: pregion
75 CHARACTER(CHRLEN) :: rcsidentstring
76 INTEGER :: icg,indcp,indmol
77 REAL(RFREAL) :: cp,
d,mw,p,
g,gc,u,
v,w,
x
78 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pgv
80 TYPE(t_grid),
POINTER :: pgrid
87 rcsidentstring =
'$RCSfile: RFLU_InitFlowHardCodeLim.F90,v $ $Revision: 1.4 $'
89 global => pregion%global
92 'RFLU_InitFlowHardCodeLim.F90')
94 IF ( global%verbLevel > verbose_none )
THEN
95 WRITE(stdout,
'(A,1X,A)') solver_name, &
96 'Initializing flow field from limited hard code...'
98 IF ( global%verbLevel > verbose_low )
THEN
99 WRITE(stdout,
'(A,3X,A,A)') solver_name,
'Case: ',trim(global%casename)
107 pgrid => pregion%grid
108 pcv => pregion%mixt%cv
109 pgv => pregion%mixt%gv
110 pmixtinput => pregion%mixtInput
112 indcp = pregion%mixtInput%indCp
113 indmol = pregion%mixtInput%indMol
119 SELECT CASE ( pmixtinput%fluidModel )
125 CASE ( fluid_model_incomp )
126 pregion%mixt%cvState = cv_mixt_state_prim
129 CALL
errorstop(global,err_reached_default,__line__)
136 CASE ( fluid_model_comp )
137 pregion%mixt%cvState = cv_mixt_state_cons
139 SELECT CASE ( global%casename )
146 DO icg = 1,pgrid%nCellsTot
147 x = pgrid%cofg(xcoord,icg)
149 IF (
x < pmixtinput%prepRealVal1 )
THEN
150 d = pmixtinput%prepRealVal2
151 u = pmixtinput%prepRealVal3
154 p = pmixtinput%prepRealVal4
156 mw = pgv(gv_mixt_mol,indmol*icg)
157 cp = pgv(gv_mixt_cp ,indcp *icg)
162 pcv(cv_mixt_dens,icg) =
d
163 pcv(cv_mixt_xmom,icg) =
d*u
164 pcv(cv_mixt_ymom,icg) =
d*
v
165 pcv(cv_mixt_zmom,icg) =
d*w
176 CASE (
"skews_ms2p0",
"skews_ms3p0",
"skews_ms4p0" )
177 DO icg = 1,pgrid%nCellsTot
178 x = pgrid%cofg(xcoord,icg)
180 IF (
x < pmixtinput%prepRealVal1 )
THEN
181 d = pmixtinput%prepRealVal2
182 u = pmixtinput%prepRealVal3
185 p = pmixtinput%prepRealVal4
187 mw = pgv(gv_mixt_mol,indmol*icg)
188 cp = pgv(gv_mixt_cp ,indcp *icg)
193 pcv(cv_mixt_dens,icg) =
d
194 pcv(cv_mixt_xmom,icg) =
d*u
195 pcv(cv_mixt_ymom,icg) =
d*
v
196 pcv(cv_mixt_zmom,icg) =
d*w
206 DO icg = 1,pgrid%nCellsTot
207 x = pgrid%cofg(xcoord,icg)
209 IF (
x < pmixtinput%prepRealVal1 )
THEN
210 d = pmixtinput%prepRealVal2
211 u = pmixtinput%prepRealVal3
214 p = pmixtinput%prepRealVal4
216 mw = pgv(gv_mixt_mol,indmol*icg)
217 cp = pgv(gv_mixt_cp ,indcp *icg)
222 pcv(cv_mixt_dens,icg) =
d
223 pcv(cv_mixt_xmom,icg) =
d*u
224 pcv(cv_mixt_ymom,icg) =
d*
v
225 pcv(cv_mixt_zmom,icg) =
d*w
235 CALL
errorstop(global,err_reached_default,__line__)
243 CALL
errorstop(global,err_reached_default,__line__)
250 IF ( global%verbLevel > verbose_none )
THEN
251 WRITE(stdout,
'(A,1X,A)') solver_name, &
252 'Initializing flow field from limited hard code done.'
subroutine rflu_initflowhardcodelim(pRegion)
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_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)