Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TURB_rFLO_ReadSolution.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: read in turbulence solution.
26 !
27 ! Description: the following solution formats are supported:
28 ! - RocfloMP ASCII
29 ! - RocfloMP binary.
30 !
31 ! Input: regions = dimensions of all regions.
32 !
33 ! Output:
34 ! globalClass LES : region%levels%mixt%tv = turbulent viscosity
35 ! globalClass RANS : no yet defined
36 ! global%currentTime = physical time
37 ! global%resInit = initial residual
38 !
39 ! Notes: solution is read in only for the current grid level;
40 ! solution is also read in for all dummy cells.
41 !
42 !******************************************************************************
43 !
44 ! $Id: TURB_rFLO_ReadSolution.F90,v 1.7 2009/08/26 12:28:53 mtcampbe Exp $
45 !
46 ! Copyright: (c) 2001 by the University of Illinois
47 !
48 !******************************************************************************
49 
50 SUBROUTINE turb_rflo_readsolution( regions ) ! PUBLIC
51 
52  USE moddatatypes
53  USE moddatastruct, ONLY : t_region
54  USE modglobal, ONLY : t_global
57  USE moderror
58  USE modmpi
59  USE modparameters
61  IMPLICIT NONE
62 
63 #include "Indexing.h"
64 
65 ! ... parameters
66  TYPE(t_region), POINTER :: regions(:)
67 
68 ! ... loop variables
69  INTEGER :: ireg, i, j, k, n
70 
71 ! ... local variables
72  CHARACTER(2*CHRLEN+17) :: fname
73  CHARACTER(CHRLEN) :: msg, timestring
74  LOGICAL :: fileexists
75 
76 #ifdef MPI
77  INTEGER :: status(mpi_status_size)
78 #endif
79  INTEGER :: ilev, iregfile, ipc, jpc, kpc, ndumcells, nfield, ioff, ijoff, ijk
80  INTEGER :: idcbeg, jdcbeg, kdcbeg, idcend, jdcend, kdcend, ijkbeg, ijkend
81  INTEGER :: ndimc, nrvar, noutsol, globalclass, errorflag
82  INTEGER, ALLOCATABLE :: ivar(:,:)
83 
84  REAL(RFREAL), POINTER :: tv(:,:), tcv(:,:)
85  REAL(RFREAL), ALLOCATABLE :: rvar(:,:), solfile(:,:)
86 
87  TYPE(t_global), POINTER :: global
88 
89 !******************************************************************************
90 
91  global => regions(1)%global
92 
93  CALL registerfunction( global,'TURB_RFLO_ReadSolution',&
94  'TURB_rFLO_ReadSolution.F90' )
95 
96 ! allocate fixed-size temporary data arrays -----------------------------------
97 
98  nrvar = 4
99 
100  ALLOCATE( ivar(6,1),stat=errorflag )
101  ALLOCATE( rvar(nrvar,1),stat=errorflag )
102  global%error = errorflag
103  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
104 
105 ! copy time to string ---------------------------------------------------------
106 
107  IF (global%flowType == flow_unsteady) THEN
108  WRITE(timestring,'(1PE11.5)') global%timeStamp
109  ELSE
110  WRITE(timestring,'(1PE11.5)') 0._rfreal
111  ENDIF
112 
113 ! open solution file (only master proc.) --------------------------------------
114 
115  IF (global%myProcid == masterproc) THEN
116 
117 ! - unsteady flow
118 
119  IF (global%flowType == flow_unsteady) THEN
120  IF (global%solutFormat == format_ascii) THEN
121  WRITE(fname,'(A,1PE11.5)') trim(global%inDir)//trim(global%casename)//'.turba_', &
122  global%timeStamp
123  INQUIRE(file=fname,exist=fileexists)
124  IF (fileexists .EQV. .true.) &
125  OPEN(if_solut,file=fname,form='formatted',status='old',iostat=errorflag)
126  ELSE IF (global%solutFormat == format_binary) THEN
127  WRITE(fname,'(A,1PE11.5)') trim(global%inDir)//trim(global%casename)//'.turbb_', &
128  global%timeStamp
129  INQUIRE(file=fname,exist=fileexists)
130  IF (fileexists .EQV. .true.) &
131  OPEN(if_solut,file=fname,form='unformatted',status='old',iostat=errorflag)
132  ELSE
133  CALL errorstop( global,err_unknown_format,__line__ )
134  ENDIF
135 
136 ! - steady flow
137 
138  ELSE
139  IF (global%solutFormat == format_ascii) THEN
140  WRITE(fname,'(A,I6.6)') trim(global%inDir)//trim(global%casename)//'.turba_', &
141  global%currentIter
142  INQUIRE(file=fname,exist=fileexists)
143  IF (fileexists .EQV. .true.) &
144  OPEN(if_solut,file=fname,form='formatted',status='old',iostat=errorflag)
145  ELSE IF (global%solutFormat == format_binary) THEN
146  WRITE(fname,'(A,I6.6)') trim(global%inDir)//trim(global%casename)//'.turbb_', &
147  global%currentIter
148  INQUIRE(file=fname,exist=fileexists)
149  IF (fileexists .EQV. .true.) &
150  OPEN(if_solut,file=fname,form='unformatted',status='old',iostat=errorflag)
151  ELSE
152  CALL errorstop( global,err_unknown_format,__line__ )
153  ENDIF
154  ENDIF
155 
156  IF (fileexists .EQV. .true.) THEN
157  global%error = errorflag
158  IF (global%error /= 0) &
159  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
160 
161  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) &
162  WRITE(stdout,'(A)') solver_name//' - turbulence'
163  ELSE
164  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) &
165  WRITE(stdout,'(A)') solver_name//' Start new turbulence ...'
166  ENDIF
167 
168  ENDIF ! MASTERPROC
169 
170 #ifdef MPI
171  CALL mpi_bcast( fileexists,1,mpi_logical,masterproc,global%mpiComm,global%mpierr )
172  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
173 #endif
174 
175  IF (.NOT. (fileexists .eqv. .true.)) THEN
176  goto 999
177  ENDIF
178 
179 ! read & broadcast time and initial residual in file --------------------------
180 
181  IF (global%myProcid == masterproc) THEN
182  CALL rflo_readdatafilereal( global,if_solut,global%solutFormat,nrvar,1,rvar )
183  ENDIF
184 
185 #ifdef MPI
186  CALL mpi_bcast( rvar,nrvar,mpi_rfreal,masterproc,global%mpiComm,global%mpierr )
187  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
188 #endif
189 
190  IF (global%flowType==flow_unsteady .AND. global%currentTime>0._rfreal) THEN
191  IF (global%currentTime /= rvar(1,1)) THEN
192  WRITE(msg,1000) rvar(1,1),global%currentTime
193  CALL errorstop( global,err_time_solution,__line__,msg//' File: '//trim(fname) )
194  ENDIF
195  ELSE
196  global%currentTime = rvar(1,1)
197  ENDIF
198  global%resInit = rvar(2,1)
199  global%esg1Sum = rvar(3,1)
200  global%esg4Sum = rvar(4,1)
201 
202 ! read solution data ----------------------------------------------------------
203 
204 ! first define no.of output solution by subsquent selection (order matters)
205 
206  DO ireg=1,global%nRegions
207  IF (regions(ireg)%procid == global%myProcid) THEN
208  IF (regions(ireg)%turbInput%modelClass == model_les) THEN
209  globalclass = model_les
210  ENDIF
211  ENDIF
212  ENDDO
213 
214  DO ireg=1,global%nRegions
215  IF (regions(ireg)%procid == global%myProcid) THEN
216  IF ((regions(ireg)%mixtInput%turbModel == turb_model_sa) .OR. &
217  (regions(ireg)%mixtInput%turbModel == turb_model_dessa) .OR. &
218  (regions(ireg)%mixtInput%turbModel == turb_model_hdessa)) THEN
219  globalclass = model_rans
220  ENDIF
221  ENDIF
222  ENDDO
223 
224  DO ireg=1,global%nRegions
225 
226 ! - get dimensions and pointers
227 
228  ilev = regions(ireg)%currLevel
229  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
230  jdcbeg,jdcend,kdcbeg,kdcend )
231  CALL rflo_getcelloffset( regions(ireg),ilev,ioff,ijoff )
232  ijkbeg = indijk(idcbeg,jdcbeg,kdcbeg,ioff,ijoff)
233  ijkend = indijk(idcend,jdcend,kdcend,ioff,ijoff)
234  ndimc = ijkend - ijkbeg + 1
235 
236 ! - read region number and dimensions (only master)
237 
238  IF (global%myProcid == masterproc) THEN
239  CALL rflo_readdatafileint( global,if_solut,global%solutFormat,6,1,ivar )
240  iregfile = ivar(1,1)
241  ipc = ivar(2,1)
242  jpc = ivar(3,1)
243  kpc = ivar(4,1)
244  ndumcells = ivar(5,1)
245  nfield = ivar(6,1)
246 
247  IF (iregfile /= ireg) &
248  CALL errorstop( global,err_region_number,__line__,'File: '//trim(fname) )
249  IF ((ipc /= regions(ireg)%levels(ilev)%grid%ipc) .OR. &
250  (jpc /= regions(ireg)%levels(ilev)%grid%jpc) .OR. &
251  (kpc /= regions(ireg)%levels(ilev)%grid%kpc)) THEN
252  WRITE(msg,1005) ireg,ipc,jpc,kpc
253  CALL errorstop( global,err_grid_dimensions,__line__,msg )
254  ENDIF
255  IF (ndumcells /= regions(ireg)%nDumCells) THEN
256  WRITE(msg,1010) ireg,ndumcells,regions(ireg)%nDumCells
257  CALL errorstop( global,err_grid_dumcells,__line__,msg )
258  ENDIF
259  ENDIF
260 
261 ! - master reads & sends data, others receive them
262 
263  IF (global%myProcid == masterproc) THEN
264 
265  noutsol = nfield
266  ALLOCATE( solfile(noutsol,ndimc),stat=errorflag )
267  global%error = errorflag
268  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
269 
270  CALL rflo_readdatafilereal( global,if_solut,global%solutFormat, &
271  noutsol,ndimc,solfile )
272 
273 #ifdef MPI
274  IF (regions(ireg)%procid /= masterproc) THEN
275  CALL mpi_send( noutsol,1,mpi_integer, &
276  regions(ireg)%procid,ireg, &
277  global%mpiComm,global%mpierr )
278  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
279  CALL mpi_send( solfile,noutsol*ndimc,mpi_rfreal, &
280  regions(ireg)%procid,ireg, &
281  global%mpiComm,global%mpierr )
282  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
283  ENDIF
284 #endif
285 
286  ELSE ! not the master
287 
288  IF (regions(ireg)%procid == global%myProcid) THEN
289 #ifdef MPI
290  CALL mpi_recv( noutsol,1,mpi_integer,masterproc,ireg, &
291  global%mpiComm,status,global%mpierr )
292  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
293 #endif
294  ALLOCATE( solfile(noutsol,ndimc),stat=errorflag )
295  global%error = errorflag
296  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
297 
298 #ifdef MPI
299  CALL mpi_recv( solfile,noutsol*ndimc,mpi_rfreal,masterproc,ireg, &
300  global%mpiComm,status,global%mpierr )
301  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
302 #endif
303  ENDIF
304 
305  ENDIF
306 
307 ! - copy solution into data structure
308 
309  IF (regions(ireg)%procid == global%myProcid) THEN
310  IF (regions(ireg)%turbInput%modelClass == model_les) THEN
311  tv => regions(ireg)%levels(ilev)%mixt%tv
312  n = 0
313  DO k=kdcbeg,kdcend
314  DO j=jdcbeg,jdcend
315  DO i=idcbeg,idcend
316  n = n + 1
317  ijk = indijk(i,j,k,ioff,ijoff)
318  tv(tv_mixt_muet,ijk) = solfile(1,n)
319  ENDDO
320  ENDDO
321  ENDDO
322  ENDIF
323  IF ((regions(ireg)%mixtInput%turbModel == turb_model_sa) .OR. &
324  (regions(ireg)%mixtInput%turbModel == turb_model_dessa) .OR. &
325  (regions(ireg)%mixtInput%turbModel == turb_model_hdessa)) THEN
326  tcv => regions(ireg)%levels(ilev)%turb%cv
327  n = 0
328  DO k=kdcbeg,kdcend
329  DO j=jdcbeg,jdcend
330  DO i=idcbeg,idcend
331  n = n + 1
332  ijk = indijk(i,j,k,ioff,ijoff)
333  tcv(cv_sa_nutil,ijk) = solfile(1,n)
334  ENDDO
335  ENDDO
336  ENDDO
337  ENDIF ! turbModel/modelClass
338  ENDIF ! global%myProcid
339 
340  IF (ALLOCATED(solfile).eqv..true.) THEN
341  DEALLOCATE( solfile,stat=errorflag )
342  global%error = errorflag
343  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
344  ENDIF
345 
346  ENDDO ! iReg
347 
348 ! finalize --------------------------------------------------------------------
349 
350  IF (global%myProcid == masterproc) THEN
351  CLOSE(if_solut,iostat=errorflag)
352  global%error = errorflag
353  IF (global%error /= 0) &
354  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
355  ENDIF
356 
357 999 CONTINUE
358 
359  CALL deregisterfunction( global )
360 
361 1000 FORMAT('Time in file is= ',1pe12.5,' but it should be= ',e12.5,'.')
362 1005 FORMAT('Region ',i5,', ipc= ',i6,', jpc= ',i6,', kpc= ',i6,'.')
363 1010 FORMAT('Region ',i5,', # dummy cells=',i2,' but should be= ',i1)
364 
365 END SUBROUTINE turb_rflo_readsolution
366 
367 !******************************************************************************
368 !
369 ! RCS Revision history:
370 !
371 ! $Log: TURB_rFLO_ReadSolution.F90,v $
372 ! Revision 1.7 2009/08/26 12:28:53 mtcampbe
373 ! Ported to Hera. Fixed logical expression syntax errors. Replaced all
374 ! IF (logical_variable) with IF (logical_variable .eqv. .true.) as
375 ! consistent with the specification. Also changed: IF( ASSOCIATED(expr) )
376 ! to IF ( ASSOCIATED(expr) .eqv. .true. ). Intel compilers produce code
377 ! which silently fails for some mal-formed expressions, so these changes
378 ! are a net which should ensure that they are evaluated as intended.
379 !
380 ! Revision 1.6 2008/12/06 08:44:45 mtcampbe
381 ! Updated license.
382 !
383 ! Revision 1.5 2008/11/19 22:17:56 mtcampbe
384 ! Added Illinois Open Source License/Copyright
385 !
386 ! Revision 1.4 2006/02/07 06:04:18 wasistho
387 ! bug fixed: broadcast fileExists before used
388 !
389 ! Revision 1.3 2006/02/06 06:13:28 wasistho
390 ! enable starting turbulence from laminar run
391 !
392 ! Revision 1.2 2005/03/09 06:37:23 wasistho
393 ! incorporated HDESSA
394 !
395 ! Revision 1.1 2004/03/11 03:26:34 wasistho
396 ! changed rocturb nomenclature
397 !
398 ! Revision 1.1 2004/03/08 23:35:46 wasistho
399 ! changed turb nomenclature
400 !
401 ! Revision 1.6 2004/02/26 21:28:07 wasistho
402 ! added esg1Sum and esg4Sum to Real heading for restart
403 !
404 ! Revision 1.5 2004/02/11 03:25:01 wasistho
405 ! added feature: variable number of turbulence output fields
406 !
407 ! Revision 1.4 2003/10/09 22:50:02 wasistho
408 ! mv call to TURB_RansSAGetEddyVis from readSolution to initSolution
409 !
410 ! Revision 1.3 2003/10/07 02:06:41 wasistho
411 ! initial installation of RaNS-SA and DES
412 !
413 ! Revision 1.2 2003/09/05 21:50:07 wasistho
414 ! removed ifdef PERI
415 !
416 ! Revision 1.1 2003/07/22 03:01:12 wasistho
417 ! prepare more accurate rocturb restart
418 !
419 !
420 !******************************************************************************
421 
422 
423 
424 
425 
426 
427 
428 
429 
**********************************************************************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 idcend
j indices k indices k
Definition: Indexing.h:6
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine rflo_readdatafileint(global, fileId, form, nDim1, nDim2, ivar)
subroutine rflo_getdimensdummy(region, iLev, idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend)
**********************************************************************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 kdcbeg
subroutine turb_rflo_readsolution(regions)
blockLoc i
Definition: read.cpp:79
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
**********************************************************************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 idcbeg
**********************************************************************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
const NT & n
**********************************************************************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 jdcend
j indices j
Definition: Indexing.h:6
**********************************************************************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 jdcbeg
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_readdatafilereal(global, fileId, form, nDim1, nDim2, var)