76 TYPE(t_region
),
POINTER :: pregion
82 CHARACTER(CHRLEN) :: rcsidentstring
83 INTEGER,
PARAMETER :: max_invalid_locs = 10
84 INTEGER :: icg,indcp,indmol,nlocs
85 INTEGER :: loc(max_invalid_locs,min_val:max_val)
86 REAL(RFREAL) :: bp,bt,cg2,cl2,cpgas,cpvap,cv2,cvg,cvl,cvm,cvv,eo,p,po, &
87 rgas,rho,rhoyg,rhoyl,rhoyv,ro,rrho,rvap,t,to,u,
v,vm2,w
88 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv,pcvspec,pdv,pgv
90 TYPE(t_grid),
POINTER :: pgrid
96 rcsidentstring =
'$RCSfile: RFLU_CheckValidity_GL.F90,v $'
98 global => pregion%global
101 'RFLU_CheckValidity_GL.F90')
107 pgrid => pregion%grid
109 pcv => pregion%mixt%cv
110 pdv => pregion%mixt%dv
111 pgv => pregion%mixt%gv
114 pcvspec => pregion%spec%cv
119 indcp = pregion%mixtInput%indCp
120 indmol = pregion%mixtInput%indMol
122 ro = global%refDensityLiq
123 po = global%refPressLiq
124 to = global%refTempLiq
125 bp = global%refBetaPLiq
126 bt = global%refBetaTLiq
127 cvl = global%refCvLiq
129 rgas =
mixtperf_r_m(pregion%specInput%specType(1)%pMaterial%molw)
130 cvg =
mixtperf_cv_cpr(pregion%specInput%specType(1)%pMaterial%spht,rgas)
132 rvap =
mixtperf_r_m(pregion%specInput%specType(2)%pMaterial%molw)
133 cvv =
mixtperf_cv_cpr(pregion%specInput%specType(2)%pMaterial%spht,rvap)
139 DO icg = 1,pgrid%nCells
140 rho = pcv(cv_mixt_dens,icg)
141 rrho = 1.0_rfreal/rho
142 rhoyg = pcvspec(1,icg)
143 rhoyv = pcvspec(2,icg)
144 rhoyl = rho - rhoyg - rhoyv
146 u = rrho*pcv(cv_mixt_xmom,icg)
147 v = rrho*pcv(cv_mixt_ymom,icg)
148 w = rrho*pcv(cv_mixt_zmom,icg)
149 eo = rrho*pcv(cv_mixt_ener,icg)
151 vm2 = u*u +
v*
v + w*w
152 cvm = (rhoyl*cvl + rhoyv*cvv + rhoyg*cvg)/rho
159 p =
mixtgasliq_p(rhoyl,rhoyv,rhoyg,cl2,cv2,cg2,rho,ro,po,to,bp,bt,t)
161 IF ( (
isnan(rho) .EQV. .true.) .OR. &
162 (
isnan(u) .EQV. .true.) .OR. &
163 (
isnan(
v) .EQV. .true.) .OR. &
164 (
isnan(w) .EQV. .true.) .OR. &
165 (
isnan(p) .EQV. .true.) .OR. &
166 (
isnan(t) .EQV. .true.) )
THEN
169 IF ( nlocs == 1 )
THEN
170 WRITE(stdout,
'(A,1X,A,1X,I9)') solver_name, &
171 'Invalid variables detected!'
173 IF ( global%flowType == flow_unsteady )
THEN
174 WRITE(stdout,
'(A,3X,A,1X,1PE12.5)') solver_name,
'Current time:', &
177 WRITE(stdout,
'(A,3X,A,1X,I6)') solver_name, &
178 'Current iteration number:', &
182 WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', &
183 pregion%iRegionGlobal
184 WRITE(stdout,
'(A,6X,A,6(1X,A))') solver_name,
'#', &
193 IF ( nlocs <= max_invalid_locs )
THEN
194 WRITE(stdout,
'(A,4X,I3,6(1X,E13.6))') solver_name,nlocs, &
196 loc(nlocs,min_val:max_val) = icg
205 IF ( nlocs > 0 )
THEN
206 IF ( nlocs > max_invalid_locs )
THEN
207 WRITE(stdout,
'(A,3X,A,1X,I3,1X,A,1X,I9,1X,A)') solver_name, &
208 'Only wrote the first',max_invalid_locs,
'of',nlocs, &
209 'cells with invalid variables.'
211 locinfo_mode_silent,output_mode_anybody)
214 locinfo_mode_silent,output_mode_anybody)
217 CALL
errorstop(global,err_invalid_value,__line__)
real(rfreal) function mixtperf_r_m(M)
subroutine registerfunction(global, funName, fileName)
real(rfreal) function mixtgasliq_p(DYl, DYv, DYg, Cl2, Cv2, Cg2, D, Dz, Po, To, Bp, Bt, T)
*********************************************************************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_c2_grt(G, R, T)
real(rfreal) function mixtliq_c2_bp(Bp)
subroutine rflu_printlocinfo(pRegion, locUnsorted, nLocUnsorted, locInfoMode, outputMode)
subroutine errorstop(global, errorCode, errorLine, addMessage)
real(rfreal) function mixtperf_t_cveovm2(Cv, Eo, Vm2)
subroutine deregisterfunction(global)
real(rfreal) function mixtperf_cv_cpr(Cp, R)
subroutine rflu_checkvalidity_gl(pRegion)