66 TYPE(t_region
),
POINTER :: pregion
72 CHARACTER(CHRLEN) :: rcsidentstring
73 INTEGER :: errorflag,ispec,nspecies,upplim
75 INTEGER,
DIMENSION(:,:),
ALLOCATABLE :: loc
76 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: pcv
77 TYPE(t_grid),
POINTER :: pgrid
80 rcsidentstring =
'$RCSfile: SPEC_RFLU_PrintFlowInfo.F90,v $ $Revision: 1.3 $'
86 global => pregion%global
89 'SPEC_RFLU_PrintFlowInfo.F90')
91 IF ( global%verbLevel > verbose_none )
THEN
92 WRITE(stdout,
'(A,1X,A)') solver_name,
'Printing species information...'
93 WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', &
95 IF ( global%flowType == flow_unsteady )
THEN
96 WRITE(stdout,
'(A,3X,A,1X,1PE11.5)') solver_name,
'Current time:', &
105 pcv => pregion%spec%cv
106 pgrid => pregion%grid
112 nspecies = pregion%specInput%nSpecies
114 ALLOCATE(loc(nspecies,min_val:max_val),stat=errorflag)
115 global%error = errorflag
116 IF ( global%error /= err_none )
THEN
117 CALL
errorstop(global,err_allocate,__line__,
'loc')
124 upplim = pgrid%nCells
132 DO ispec = 1,nspecies
133 dummy = minloc(pcv(ispec,1:upplim))
134 loc(ispec,min_val) = dummy(1)
136 dummy = maxloc(pcv(ispec,1:upplim))
137 loc(ispec,max_val) = dummy(1)
144 DO ispec = 1,nspecies
145 WRITE(stdout,
'(A,3X,A,2(1X,E23.16),2(1X,I9))') &
146 solver_name,
'Density (kg/m^3):', &
147 minval(pcv(ispec,1:upplim)),maxval(pcv(ispec,1:upplim)), &
148 loc(ispec,min_val),loc(ispec,max_val)
155 IF ( global%verbLevel /= verbose_low )
THEN
157 output_mode_master_only)
164 DEALLOCATE(loc,stat=errorflag)
165 global%error = errorflag
166 IF ( global%error /= err_none )
THEN
167 CALL
errorstop(global,err_deallocate,__line__,
'loc')
174 IF ( global%verbLevel > verbose_none )
THEN
175 WRITE(stdout,
'(A,1X,A)') solver_name,
'Printing species information done.'
subroutine registerfunction(global, funName, fileName)
subroutine spec_rflu_printflowinfo(pRegion)
subroutine rflu_printlocinfo(pRegion, locUnsorted, nLocUnsorted, locInfoMode, outputMode)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)