72 TYPE(t_region
),
POINTER :: pregion
78 CHARACTER(CHRLEN) :: rcsidentstring
79 INTEGER :: cvmixtpres,cvmixtxvel,cvmixtyvel,cvmixtzvel,icg,indcp,indmol
80 REAL(RFREAL) :: cp,cvm,cvg,cvv,eo,
g,gc,mw,
r,rhog,rhol,rhov,rg,rv,vm2,yg,yl,yv
81 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pgv
89 rcsidentstring =
'$RCSfile: RFLU_InitFlowScratch.F90,v $'
91 global => pregion%global
94 'RFLU_InitFlowScratch.F90')
96 IF ( global%verbLevel > verbose_none )
THEN
97 WRITE(stdout,
'(A,1X,A)') solver_name, &
98 'Initializing flow field from scratch...'
105 pcv => pregion%mixt%cv
106 pgv => pregion%mixt%gv
107 pmixtinput => pregion%mixtInput
109 indcp = pregion%mixtInput%indCp
110 indmol = pregion%mixtInput%indMol
116 SELECT CASE ( pmixtinput%fluidModel )
122 CASE ( fluid_model_incomp )
123 pregion%mixt%cvState = cv_mixt_state_prim
125 cvmixtxvel =
rflu_getcvloc(global,pmixtinput%fluidModel,cv_mixt_xvel)
126 cvmixtyvel =
rflu_getcvloc(global,pmixtinput%fluidModel,cv_mixt_yvel)
127 cvmixtzvel =
rflu_getcvloc(global,pmixtinput%fluidModel,cv_mixt_zvel)
128 cvmixtpres =
rflu_getcvloc(global,pmixtinput%fluidModel,cv_mixt_pres)
130 DO icg = 1,pregion%grid%nCellsTot
131 pcv(cvmixtxvel,icg) = pregion%mixtInput%iniVelX
132 pcv(cvmixtyvel,icg) = pregion%mixtInput%iniVelY
133 pcv(cvmixtzvel,icg) = pregion%mixtInput%iniVelZ
134 pcv(cvmixtpres,icg) = pregion%mixtInput%iniPress
141 CASE ( fluid_model_comp )
142 pregion%mixt%cvState = cv_mixt_state_cons
144 SELECT CASE ( pregion%mixtInput%gasModel )
150 CASE ( gas_model_tcperf, &
152 gas_model_mixt_tcperf, &
153 gas_model_mixt_tperf, &
154 gas_model_mixt_pseudo )
155 DO icg = 1,pregion%grid%nCellsTot
156 mw = pgv(gv_mixt_mol,indmol*icg)
157 cp = pgv(gv_mixt_cp ,indcp *icg)
162 r = pregion%mixtInput%iniDens
164 pcv(cv_mixt_dens,icg) =
r
165 pcv(cv_mixt_xmom,icg) =
r*pregion%mixtInput%iniVelX
166 pcv(cv_mixt_ymom,icg) =
r*pregion%mixtInput%iniVelY
167 pcv(cv_mixt_zmom,icg) =
r*pregion%mixtInput%iniVelZ
170 pregion%mixtInput%iniPress, &
171 pregion%mixtInput%iniVelX, &
172 pregion%mixtInput%iniVelY, &
173 pregion%mixtInput%iniVelZ)
175 pcv(cv_mixt_ener,icg) = pcv(cv_mixt_dens,icg)*eo
182 CASE ( gas_model_mixt_gasliq )
183 rg =
mixtperf_r_m(pregion%specInput%specType(1)%pMaterial%molw)
186 rv =
mixtperf_r_m(pregion%specInput%specType(2)%pMaterial%molw)
190 global%refBetaPLiq, &
191 global%refBetaTLiq, &
192 pregion%mixtInput%iniPress, &
193 global%refPressLiq, &
194 pregion%mixtInput%iniTemp, &
197 DO icg = 1,pregion%grid%nCellsTot
198 yg = pregion%specInput%specType(1)%initVal
199 yv = pregion%specInput%specType(2)%initVal
200 yl = 1.0_rfreal - yg - yv
203 pregion%mixtInput%iniTemp)
205 pregion%mixtInput%iniTemp)
207 r = 1.0_rfreal/(yg/rhog + yv/rhov + yl/rhol)
209 pcv(cv_mixt_dens,icg) =
r
210 pcv(cv_mixt_xmom,icg) =
r*pregion%mixtInput%iniVelX
211 pcv(cv_mixt_ymom,icg) =
r*pregion%mixtInput%iniVelY
212 pcv(cv_mixt_zmom,icg) =
r*pregion%mixtInput%iniVelZ
214 cvm = yg*cvg + yv*cvv + yl*global%refCvLiq
216 vm2 = pregion%mixtInput%iniVelX*pregion%mixtInput%iniVelX &
217 + pregion%mixtInput%iniVelY*pregion%mixtInput%iniVelY &
218 + pregion%mixtInput%iniVelZ*pregion%mixtInput%iniVelZ
220 pcv(cv_mixt_ener,icg) = pcv(cv_mixt_dens,icg)* &
229 CALL
errorstop(global,err_reached_default,__line__)
237 CALL
errorstop(global,err_reached_default,__line__)
244 IF ( global%verbLevel > verbose_none )
THEN
245 WRITE(stdout,
'(A,1X,A)') solver_name, &
246 'Initializing flow field from scratch done.'
INTEGER function rflu_getcvloc(global, fluidModel, var)
real(rfreal) function mixtperf_r_m(M)
subroutine registerfunction(global, funName, fileName)
real(rfreal) function mixtperf_d_prt(P, R, T)
subroutine rflu_initflowscratch(pRegion)
real(rfreal) function mixtgasliq_eo_cvmtvm2(Cvm, T, Vm2)
real(rfreal) function mixtliq_d_dobpppobttto(Dz, Bp, Bt, P, Po, T, To)
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)