61 TYPE(t_region
),
POINTER :: region
67 CHARACTER(CHRLEN) :: errorstring,ifilename,sectionstring,rcsidentstring, &
68 timestring1,timestring2
72 INTEGER :: errorflag,ifile,loopcounter,ncellstot,ncellsexpected,nvars, &
73 nvarsexpected,precactual,precexpected,rangeactual,rangeexpected
74 REAL(RFREAL) :: currenttime
75 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: tv, tcv, vort
76 REAL(RFREAL),
DIMENSION(:),
POINTER :: lens
82 rcsidentstring =
'$RCSfile: TURB_rFLU_ReadSolutionBinary.F90,v $ $Revision: 1.6 $'
84 global => region%global
86 'TURB_rFLU_ReadSolutionBinary.F90')
92 IF ( global%myProcid == masterproc .AND. &
93 global%verbLevel > verbose_none )
THEN
94 WRITE(stdout,
'(A,1X,A)') solver_name,
'Reading binary turbulence file...'
97 IF ( global%flowType == flow_unsteady )
THEN
98 currenttime = global%currentTime
101 region%iRegionGlobal,currenttime,ifilename)
103 IF ( global%myProcid == masterproc .AND. &
104 global%verbLevel > verbose_none )
THEN
105 WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', &
107 WRITE(stdout,
'(A,3X,A,1X,1PE11.5)') solver_name,
'Current time:', &
112 region%iRegionGlobal,global%currentIter,ifilename)
114 IF ( global%myProcid == masterproc .AND. &
115 global%verbLevel > verbose_none )
THEN
116 WRITE(stdout,
'(A,3X,A,1X,I5.5)') solver_name,
'Global region:', &
118 WRITE(stdout,
'(A,3X,A,1X,I6.6)') solver_name,
'Current iteration '// &
119 'number:',global%currentIter
124 OPEN(ifile,file=ifilename,
form=
"FORMATTED",
status=
"OLD", &
126 global%error = errorflag
127 IF ( global%error /= err_none )
THEN
128 CALL
errorstop(global,err_file_open,__line__,ifilename)
135 IF ( global%myProcid == masterproc .AND. &
136 global%verbLevel > verbose_low )
THEN
137 WRITE(stdout,
'(A,3X,A)') solver_name,
'Header information...'
140 READ(ifile) sectionstring
141 IF ( trim(sectionstring) /=
'# ROCTURB solution file' )
THEN
142 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
149 READ(ifile) sectionstring
150 IF ( trim(sectionstring) /=
'# Precision and range' )
THEN
151 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
155 rangeexpected = range(1.0_rfreal)
157 READ(ifile) precactual,rangeactual
158 IF ( precactual < precexpected .OR. rangeactual < rangeexpected )
THEN
159 CALL
errorstop(global,err_prec_range,__line__)
166 READ(ifile) sectionstring
167 IF ( trim(sectionstring) /=
'# Initial residual' )
THEN
168 CALL
errorstop(global,err_invalid_marker,__line__,ifilename)
171 READ(ifile) global%resInit
173 READ(ifile) sectionstring
174 IF ( trim(sectionstring) /=
'# Physical time' )
THEN
175 CALL
errorstop(global,err_invalid_marker,__line__,ifilename)
178 READ(ifile) currenttime
180 IF ( global%flowType == flow_unsteady )
THEN
181 IF ( global%currentTime < 0.0_rfreal )
THEN
182 global%currentTime = currenttime
184 WRITE(timestring1,
'(1PE11.5)') global%currentTime
185 WRITE(timestring2,
'(1PE11.5)') currenttime
186 IF ( trim(timestring1) /= trim(timestring2) )
THEN
187 CALL
errorstop(global,err_time_solution,__line__,trim(ifilename))
192 READ(ifile) sectionstring
193 IF ( trim(sectionstring) /=
'# Esg1Sum' )
THEN
194 CALL
errorstop(global,err_invalid_marker,__line__,ifilename)
197 READ(ifile) global%esg1Sum
199 READ(ifile) sectionstring
200 IF ( trim(sectionstring) /=
'# Esg4Sum' )
THEN
201 CALL
errorstop(global,err_invalid_marker,__line__,ifilename)
204 READ(ifile) global%esg4Sum
212 nvarsexpected = region%turbInput%nOutField
213 ncellsexpected =
grid%nCellsTot
215 READ(ifile) sectionstring
216 IF ( trim(sectionstring) /=
'# Dimensions' )
THEN
217 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
220 READ(ifile) ncellstot,nvars
221 IF ( ncellstot /= ncellsexpected )
THEN
222 WRITE(errorstring,
'(A,1X,I6,1X,A,1X,I6))')
'Specified:',ncellstot, &
223 'but expected:',ncellsexpected
224 CALL
errorstop(global,err_invalid_ncells,__line__,errorstring)
227 IF ( nvars /= nvarsexpected )
THEN
228 WRITE(errorstring,
'(A,1X,I6,1X,A,1X,I6))')
'Specified:',nvars, &
229 'but expected:',nvarsexpected
230 CALL
errorstop(global,err_invalid_nvars,__line__)
241 loopcounter = loopcounter + 1
243 READ(ifile) sectionstring
245 SELECT CASE ( trim(sectionstring) )
251 CASE (
'# Eddy viscosity' )
252 IF ( global%myProcid == masterproc .AND. &
253 global%verbLevel > verbose_low )
THEN
254 WRITE(stdout,
'(A,3X,A)') solver_name,
'Eddy viscosity...'
257 IF (region%turbInput%modelClass == model_les)
THEN
261 READ(ifile) (tv(tv_mixt_muet,
j),
j=1,
grid%nCellsTot)
263 IF (
ASSOCIATED( region%turb%postv ) .eqv. .true.)
THEN
264 region%turb%postv(1,:) = tv(tv_mixt_muet,:)
266 ELSEIF (region%turbInput%modelClass == model_rans)
THEN
267 tcv => region%turb%cv
270 READ(ifile) (tcv(cv_sa_nutil,
j),
j=1,
grid%nCellsTot)
272 IF (
ASSOCIATED( region%turb%postv ).eqv..true.)
THEN
273 region%turb%postv(1,:) = tcv(cv_sa_nutil,:)
281 CASE (
'# Total vorticity' )
282 IF ( global%myProcid == masterproc .AND. &
283 global%verbLevel > verbose_low )
THEN
284 WRITE(stdout,
'(A,3X,A)') solver_name,
'Total vorticity...'
287 vort => region%turb%vort
290 READ(ifile) (vort(xcoord,
j),
j=1,
grid%nCellsTot)
296 CASE (
'# RANS length scale' )
297 IF ( global%myProcid == masterproc .AND. &
298 global%verbLevel > verbose_low )
THEN
299 WRITE(stdout,
'(A,3X,A)') solver_name,
'RaNS length scale...'
302 lens => region%turb%lens
305 READ(ifile) (lens(
j),
j=1,
grid%nCellsTot)
307 IF (
ASSOCIATED( region%turb%postv ).eqv..true.)
THEN
308 region%turb%postv(2,:) = lens(:)
316 IF ( global%myProcid == masterproc .AND. &
317 global%verbLevel > verbose_low )
THEN
318 WRITE(stdout,
'(A,3X,A)') solver_name,
'End marker...'
328 IF ( global%verbLevel > verbose_low )
THEN
329 WRITE(stdout,
'(A,3X,A)') solver_name,sectionstring
332 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
340 IF ( loopcounter >= limit_infinite_loop )
THEN
341 CALL
errorstop(global,err_infinite_loop,__line__)
350 IF ( ivars /= nvars )
THEN
351 CALL
errorstop(global,err_invalid_nvars,__line__)
358 CLOSE(ifile,iostat=errorflag)
359 global%error = errorflag
360 IF ( global%error /= err_none )
THEN
361 CALL
errorstop(global,err_file_close,__line__,ifilename)
364 IF ( global%myProcid == masterproc .AND. &
365 global%verbLevel > verbose_none )
THEN
366 WRITE(stdout,
'(A,1X,A)') solver_name,
'Reading binary turbulence file done.'
subroutine registerfunction(global, funName, fileName)
int status() const
Obtain the status of the attribute.
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com 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 **********************************************************************INTERFACE SUBROUTINE form
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine turb_rflu_readsolutionbinary(region)
subroutine deregisterfunction(global)
subroutine buildfilenamesteady(global, dest, ext, id, it, fileName)
subroutine buildfilenameunsteady(global, dest, ext, id, tm, fileName)