70 CHARACTER(CHRLEN) :: errorstring,ifilename,sectionstring,rcsidentstring, &
71 timestring1,timestring2
72 INTEGER :: errorflag,icont,ifile,ifl,imass,ipatch,ivars,
j,loopcounter,ncont, &
73 npcls,npclsexpected,nvars,nvarsexpected,precactual,precexpected, &
74 rangeactual,rangeexpected
75 INTEGER,
DIMENSION(:,:),
POINTER :: paiv
76 REAL(RFREAL) :: currenttime
77 REAL(RFREAL),
DIMENSION(:,:),
POINTER :: parv,pcv
78 TYPE(t_grid),
POINTER :: pgrid
80 TYPE(t_patch),
POINTER :: ppatch
81 TYPE(t_plag),
POINTER :: pplag
88 TYPE(t_region
),
POINTER :: pregion
94 rcsidentstring =
'$RCSfile: PLAG_RFLU_ReadSolutionASCII.F90,v $ $Revision: 1.10 $'
96 global => pregion%global
99 'PLAG_RFLU_ReadSolutionASCII.F90')
101 IF ( global%myProcid == masterproc .AND. &
102 global%verbLevel > verbose_none )
THEN
103 WRITE(stdout,
'(A,1X,A)') solver_name,
'Reading ASCII particle file...'
107 pregion%iRegionGlobal,global%currentTime, &
111 OPEN(ifile,file=ifilename,
form=
"FORMATTED",
status=
"OLD",iostat=errorflag)
112 global%error = errorflag
113 IF ( global%error /= err_none )
THEN
114 CALL
errorstop(global,err_file_open,__line__,ifilename)
121 IF ( global%myProcid == masterproc .AND. &
122 global%verbLevel > verbose_low )
THEN
123 WRITE(stdout,
'(A,3X,A)') solver_name,
'Header information...'
126 READ(ifile,
'(A)') sectionstring
127 IF ( trim(sectionstring) /=
'# ROCFLU particle file' )
THEN
128 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
135 READ(ifile,
'(A)') sectionstring
136 IF ( trim(sectionstring) /=
'# Precision and range' )
THEN
137 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
141 rangeexpected = range(1.0_rfreal)
143 READ(ifile,
'(2(I8))') precactual,rangeactual
144 IF ( precactual < precexpected .OR. rangeactual < rangeexpected )
THEN
145 CALL
errorstop(global,err_prec_range,__line__)
152 READ(ifile,
'(A)') sectionstring
153 IF ( trim(sectionstring) /=
'# Physical time' )
THEN
154 CALL
errorstop(global,err_invalid_marker,__line__,ifilename)
157 READ(ifile,
'(E23.16)') currenttime
160 IF ( global%flowType == flow_unsteady )
THEN
161 IF ( global%currentTime < 0.0_rfreal )
THEN
162 global%currentTime = currenttime
164 WRITE(timestring1,
'(1PE11.5)') global%currentTime
165 WRITE(timestring2,
'(1PE11.5)') currenttime
166 IF ( trim(timestring1) /= trim(timestring2) )
THEN
167 CALL
errorstop(global,err_time_solution,__line__,trim(ifilename))
177 pgrid => pregion%grid
178 pplag => pregion%plag
180 ncont = pregion%plagInput%nCont
183 npclsexpected = pplag%nPcls
185 READ(ifile,
'(A)') sectionstring
186 IF ( trim(sectionstring) /=
'# Dimensions' )
THEN
187 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
190 READ(ifile,
'(2(I8))') npcls,nvars
192 IF ( npcls /= npclsexpected )
THEN
193 WRITE(errorstring,
'(A,1X,I6,1X,A,1X,I6)')
'Specified:',npcls, &
194 'but expected:',npclsexpected
195 CALL
errorstop(global,err_plag_invalid_npcls,__line__,errorstring)
198 IF ( nvars /= nvarsexpected )
THEN
199 WRITE(errorstring,
'(A,1X,I6,1X,A,1X,I6)')
'Specified:',nvars, &
200 'but expected:',nvarsexpected
201 CALL
errorstop(global,err_invalid_nvars,__line__)
213 loopcounter = loopcounter + 1
215 READ(ifile,
'(A)') sectionstring
217 SELECT CASE ( trim(sectionstring) )
223 CASE (
'# Particle x-momentum' )
224 IF ( global%myProcid == masterproc .AND. &
225 global%verbLevel > verbose_low )
THEN
226 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle x-momentum...'
229 pcv => pregion%plag%cv
232 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_xmom,
j),
j=1,pplag%nPcls)
238 CASE (
'# Particle y-momentum' )
239 IF ( global%myProcid == masterproc .AND. &
240 global%verbLevel > verbose_low )
THEN
241 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle y-momentum...'
244 pcv => pregion%plag%cv
247 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_ymom,
j),
j=1,pplag%nPcls)
253 CASE (
'# Particle z-momentum' )
254 IF ( global%myProcid == masterproc .AND. &
255 global%verbLevel > verbose_low )
THEN
256 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle z-momentum...'
259 pcv => pregion%plag%cv
262 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_zmom,
j),
j=1,pplag%nPcls)
268 CASE (
'# Particle energy' )
269 IF ( global%myProcid == masterproc .AND. &
270 global%verbLevel > verbose_low )
THEN
271 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle energy...'
274 pcv => pregion%plag%cv
277 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_ener,
j),
j=1,pplag%nPcls)
283 CASE (
'# Particle x-location' )
284 IF ( global%myProcid == masterproc .AND. &
285 global%verbLevel > verbose_low )
THEN
286 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle x-location...'
289 pcv => pregion%plag%cv
292 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_xpos,
j),
j=1,pplag%nPcls)
298 CASE (
'# Particle y-location' )
299 IF ( global%myProcid == masterproc .AND. &
300 global%verbLevel > verbose_low )
THEN
301 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle y-location...'
304 pcv => pregion%plag%cv
307 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_ypos,
j),
j=1,pplag%nPcls)
313 CASE (
'# Particle z-location' )
314 IF ( global%myProcid == masterproc .AND. &
315 global%verbLevel > verbose_low )
THEN
316 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle z-location...'
319 pcv => pregion%plag%cv
322 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_zpos,
j),
j=1,pplag%nPcls)
328 CASE (
'# Particle vapor energy' )
329 IF ( global%myProcid == masterproc .AND. &
330 global%verbLevel > verbose_low )
THEN
331 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle vapor energy...'
334 pcv => pregion%plag%cv
337 READ(ifile,
'(5(E23.16))') (pcv(cv_plag_enervapor,
j),
j=1,pplag%nPcls)
343 CASE (
'# Particle mass' )
344 IF ( global%myProcid == masterproc .AND. &
345 global%verbLevel > verbose_low )
THEN
346 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle mass...'
349 pcv => pregion%plag%cv
351 IF ( icont == 0 )
THEN
356 imass = pplag%cvPlagMass(icont)
358 READ(ifile,
'(5(E23.16))') (pcv(imass,
j),
j=1,pplag%nPcls)
364 CASE (
'# Particle superloading' )
365 IF ( global%myProcid == masterproc .AND. &
366 global%verbLevel > verbose_low )
THEN
367 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle superloading...'
370 parv => pregion%plag%arv
373 READ(ifile,
'(5(E23.16))') (parv(arv_plag_spload,
j),
j=1,pplag%nPcls)
379 CASE (
'# Particle initial identifier' )
380 IF ( global%myProcid == masterproc .AND. &
381 global%verbLevel > verbose_low )
THEN
382 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle initial identifier...'
385 paiv => pregion%plag%aiv
388 READ(ifile,
'(5(I8))') (paiv(aiv_plag_pidini,
j),
j=1,pplag%nPcls)
394 CASE (
'# Particle initial region' )
395 IF ( global%myProcid == masterproc .AND. &
396 global%verbLevel > verbose_low )
THEN
397 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle initial region...'
400 paiv => pregion%plag%aiv
403 READ(ifile,
'(5(I8))') (paiv(aiv_plag_regini,
j),
j=1,pplag%nPcls)
409 CASE (
'# Particle cell' )
410 IF ( global%myProcid == masterproc .AND. &
411 global%verbLevel > verbose_low )
THEN
412 WRITE(stdout,
'(A,3X,A)') solver_name,
'Particle cell...'
415 paiv => pregion%plag%aiv
418 READ(ifile,
'(5(I8))') (paiv(aiv_plag_icells,
j),
j=1,pplag%nPcls)
424 CASE (
'# Patch data' )
425 IF ( global%myProcid == masterproc .AND. &
426 global%verbLevel > verbose_low )
THEN
427 WRITE(stdout,
'(A,3X,A)') solver_name,
'Patch data...'
430 DO ipatch = 1,pgrid%nPatches
431 ppatch => pregion%patches(ipatch)
433 IF ( (ppatch%bcType >= bc_injection .AND. ppatch%bcType <= bc_injection + bc_range) .OR. &
434 (ppatch%bcType >= bc_inflow .AND. ppatch%bcType <= bc_inflow + bc_range) )
THEN
435 ptileplag => ppatch%tilePlag
437 DO ifl = 1,ppatch%nBFaces
438 READ(ifile,
'(2(E23.16))') ptileplag%cv(cv_tile_momnrm,ifl), &
439 ptileplag%cv(cv_tile_ener ,ifl)
443 imass = ptileplag%cvTileMass(icont)
444 READ(ifile,
'(5(E23.16))') (ptileplag%cv(imass,ifl), &
445 ifl=1,ppatch%nBFaces)
448 DO ifl = 1,ppatch%nBFaces
449 READ(ifile,
'(3(E23.16))') ptileplag%dv(dv_tile_countdown,ifl), &
450 ptileplag%dv(dv_tile_diam ,ifl), &
451 ptileplag%dv(dv_tile_spload ,ifl)
461 IF ( global%myProcid == masterproc .AND. &
462 global%verbLevel > verbose_low )
THEN
463 WRITE(stdout,
'(A,3X,A)') solver_name,
'End marker...'
473 IF ( global%verbLevel > verbose_low )
THEN
474 WRITE(stdout,
'(A,3X,A)') solver_name,sectionstring
477 CALL
errorstop(global,err_invalid_marker,__line__,sectionstring)
485 IF ( loopcounter >= limit_infinite_loop )
THEN
486 CALL
errorstop(global,err_infinite_loop,__line__)
495 IF ( ivars /= nvars )
THEN
496 CALL
errorstop(global,err_invalid_nvars,__line__)
503 CLOSE(ifile,iostat=errorflag)
504 global%error = errorflag
505 IF ( global%error /= err_none )
THEN
506 CALL
errorstop(global,err_file_close,__line__,ifilename)
509 IF ( global%myProcid == masterproc .AND. &
510 global%verbLevel > verbose_none )
THEN
511 WRITE(stdout,
'(A,1X,A)') solver_name,
'Reading ASCII particle 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 plag_rflu_readsolutionascii(pRegion)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)
subroutine buildfilenameunsteady(global, dest, ext, id, tm, fileName)