73   TYPE(t_region
), 
POINTER :: pregion
 
   79   CHARACTER(CHRLEN) :: rcsidentstring
 
   80   INTEGER, 
PARAMETER :: max_invalid_locs = 10
 
   81   INTEGER :: icg,indcp,indmol,nlocs
 
   82   INTEGER :: loc(max_invalid_locs,min_val:max_val)
 
   83   REAL(RFREAL) :: eo,gamma,p,rgas,rho,rrho,t,u,
v,vm2,w
 
   84   REAL(RFREAL), 
DIMENSION(:,:), 
POINTER :: cv,gv
 
   91   rcsidentstring = 
'$RCSfile: RFLU_CheckValidity.F90,v $ $Revision: 1.7 $' 
   93   global => pregion%global
 
   96   'RFLU_CheckValidity.F90')
 
  101   CALL fprofiler_begins(
"RFLU::CheckValidity")
 
  108   cv => pregion%mixt%cv
 
  109   gv => pregion%mixt%gv
 
  111   indcp  = pregion%mixtInput%indCp
 
  112   indmol = pregion%mixtInput%indMol 
 
  114   DO icg = 1,pregion%grid%nCells
 
  115     rho  = cv(cv_mixt_dens,icg)
 
  116     rrho = 1.0_rfreal/rho
 
  117     u    = rrho*cv(cv_mixt_xmom,icg)
 
  118     v    = rrho*cv(cv_mixt_ymom,icg)
 
  119     w    = rrho*cv(cv_mixt_zmom,icg)        
 
  120     eo   = rrho*cv(cv_mixt_ener,icg)
 
  123     vm2  = u*u + 
v*
v + w*w
 
  127     IF ( (
isnan(rho) .EQV. .true.) .OR. & 
 
  128          (
isnan(u)   .EQV. .true.) .OR. &
 
  129          (
isnan(
v)   .EQV. .true.) .OR. & 
 
  130          (
isnan(w)   .EQV. .true.) .OR. & 
 
  131          (
isnan(p)   .EQV. .true.) .OR. &
 
  132          (
isnan(t)   .EQV. .true.) ) 
THEN 
  135       IF ( nlocs == 1 ) 
THEN  
  136         WRITE(stdout,
'(A,1X,A,1X,I9)') solver_name, & 
 
  137               'Invalid variables detected!' 
  139         IF ( global%flowType == flow_unsteady ) 
THEN  
  140           WRITE(stdout,
'(A,3X,A,1X,1PE12.5)') solver_name,
'Current time:', &
 
  143           WRITE(stdout,
'(A,3X,A,1X,I6)') solver_name, &
 
  144                                          'Current iteration number:', &
 
  148         WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', & 
 
  149                                          pregion%iRegionGlobal 
 
  150         WRITE(stdout,
'(A,6X,A,6(1X,A))') solver_name,
'#', &
 
  159       IF ( nlocs <= max_invalid_locs ) 
THEN  
  160         WRITE(stdout,
'(A,4X,I3,6(1X,E13.6))') solver_name,nlocs, & 
 
  162         loc(nlocs,min_val:max_val) = icg                                   
 
  171   IF ( nlocs > 0 ) 
THEN  
  172     IF ( nlocs > max_invalid_locs ) 
THEN  
  173        WRITE(stdout,
'(A,3X,A,1X,I3,1X,A,1X,I9,1X,A)') solver_name, & 
 
  174              'Only wrote the first',max_invalid_locs,
'of',nlocs, & 
 
  175              'cells with invalid variables.'     
  177                              locinfo_mode_silent,output_mode_anybody)
 
  180                              locinfo_mode_silent,output_mode_anybody)
 
  183     CALL 
errorstop(global,err_invalid_value,__line__)   
 
  191   CALL fprofiler_ends(
"RFLU::CheckValidity")
 
real(rfreal) function mixtperf_p_deogvm2(D, Eo, G, Vm2)
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 rflu_checkvalidity(pRegion)
real(rfreal) function mixtperf_t_dpr(D, P, R)
subroutine rflu_printlocinfo(pRegion, locUnsorted, nLocUnsorted, locInfoMode, outputMode)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)
real(rfreal) function mixtperf_g_cpr(Cp, R)