Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_OpenProbeFile.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: open file(s) for probe data, write header(s).
26 !
27 ! Description: none.
28 !
29 ! Input: regions = region data (processor number, active flag)
30 ! global = probe location, flow type, restart.
31 !
32 ! Output: to file.
33 !
34 ! Notes: none.
35 !
36 !******************************************************************************
37 !
38 ! $Id: RFLO_OpenProbeFile.F90,v 1.7 2008/12/06 08:44:27 mtcampbe Exp $
39 !
40 ! Copyright: (c) 2001 by the University of Illinois
41 !
42 !******************************************************************************
43 
44 SUBROUTINE rflo_openprobefile( regions )
45 
46  USE moddatatypes
47  USE moddatastruct, ONLY : t_region
48  USE modglobal, ONLY : t_global
50  USE moderror
51  USE modparameters
52  USE modmpi
53  USE modtools, ONLY: floatless
54  IMPLICIT NONE
55 
56 #include "Indexing.h"
57 
58 ! ... parameters
59  TYPE (t_region), POINTER :: regions(:)
60 
61 ! ... loop variables
62  INTEGER :: iprobe
63 
64 ! ... local variables
65  CHARACTER(CHRLEN+9) :: fname
66 
67  INTEGER :: ireg, ilev, i, j, k, inoff, ijnoff, errorflag
68  INTEGER :: corner(8)
69  INTEGER :: ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend
70  INTEGER :: icoff, ijcoff
71  INTEGER :: iprobemax
72  INTEGER :: probeiter
73 
74  LOGICAL :: fileexists, fileappend
75 
76  REAL(RFREAL) :: xc, yc, zc, xyzhexa(3,8)
77  REAL(RFREAL), POINTER :: xyz(:,:)
78  REAL(RFREAL) :: xmin, xmax, ymin, ymax, zmin, zmax
79  REAL(RFREAL) :: xmn, xmx, ymn, ymx, zmn, zmx
80  REAL(RFREAL) :: probetime
81 
82  TYPE(t_global), POINTER :: global
83 
84 !******************************************************************************
85 
86  global => regions(1)%global
87 
88  CALL registerfunction( global,'RFLO_OpenProbeFile',&
89  'RFLO_OpenProbeFile.F90' )
90 
91 ! open file
92 
93  IF (global%nProbes > 0) THEN
94  DO iprobe=1,global%nProbes
95 
96 ! --- check if region`s number within range
97 
98  IF (global%probePos(iprobe,1)>global%nRegions) &
99  CALL errorstop( global,err_probe_location,__line__ )
100 
101 ! --- support entering 0 and coordinates
102 
103  IF (global%probePos(iprobe,1)<1) THEN
104 
105  IF (global%myProcid == 0 .AND. &
106  global%verbLevel >= verbose_med) THEN
107  WRITE(stdout,'(A,1X,A,I1,A)')solver_name,&
108  'Trying to find cell containing probe '&
109  ,iprobe,' at'
110  WRITE(stdout,'(A,1X,3(E14.5))')&
111  solver_name,global%probeXYZ(iprobe,2),&
112  global%probeXYZ(iprobe,3), &
113  global%probeXYZ(iprobe,4)
114  ENDIF
115 
116 regs: DO ireg = 1,global%nRegions
117 
118  IF (regions(ireg)%procid==global%myProcid .AND. &
119  regions(ireg)%active==active) THEN
120 
121  ilev = regions(ireg)%currLevel
122  CALL rflo_getdimensphys( regions(ireg),ilev,ipcbeg,ipcend, &
123  jpcbeg,jpcend,kpcbeg,kpcend )
124  CALL rflo_getcelloffset( regions(ireg),ilev,icoff,ijcoff )
125  CALL rflo_getnodeoffset( regions(ireg),ilev,inoff,ijnoff )
126 
127  xyz => regions(ireg)%levels(ilev)%grid%xyz
128 
129 ! --------- see if x, y, and z is within bounding box of any of my cells
130 
131  xmn = 1.0e+30
132  xmx = -1.0e+30
133  ymn = 1.0e+30
134  ymx = -1.0e+30
135  zmn = 1.0e+30
136  zmx = -1.0e+30
137  DO k=kpcbeg,kpcend
138  DO j=jpcbeg,jpcend
139  DO i=ipcbeg,ipcend
140  corner(1) = indijk(i ,j ,k ,inoff,ijnoff)
141  corner(2) = indijk(i ,j ,k+1,inoff,ijnoff)
142  corner(3) = indijk(i ,j+1,k+1,inoff,ijnoff)
143  corner(4) = indijk(i ,j+1,k ,inoff,ijnoff)
144  corner(5) = indijk(i+1,j ,k ,inoff,ijnoff)
145  corner(6) = indijk(i+1,j ,k+1,inoff,ijnoff)
146  corner(7) = indijk(i+1,j+1,k+1,inoff,ijnoff)
147  corner(8) = indijk(i+1,j+1,k ,inoff,ijnoff)
148 
149  xmin = min(xyz(1,corner(1)),xyz(1,corner(2)),xyz(1,corner(3)), &
150  xyz(1,corner(4)),xyz(1,corner(5)),xyz(1,corner(6)), &
151  xyz(1,corner(7)),xyz(1,corner(8)))
152  xmax = max(xyz(1,corner(1)),xyz(1,corner(2)),xyz(1,corner(3)), &
153  xyz(1,corner(4)),xyz(1,corner(5)),xyz(1,corner(6)), &
154  xyz(1,corner(7)),xyz(1,corner(8)))
155  ymin = min(xyz(2,corner(1)),xyz(2,corner(2)),xyz(2,corner(3)), &
156  xyz(2,corner(4)),xyz(2,corner(5)),xyz(2,corner(6)), &
157  xyz(2,corner(7)),xyz(2,corner(8)))
158  ymax = max(xyz(2,corner(1)),xyz(2,corner(2)),xyz(2,corner(3)), &
159  xyz(2,corner(4)),xyz(2,corner(5)),xyz(2,corner(6)), &
160  xyz(2,corner(7)),xyz(2,corner(8)))
161  zmin = min(xyz(3,corner(1)),xyz(3,corner(2)),xyz(3,corner(3)), &
162  xyz(3,corner(4)),xyz(3,corner(5)),xyz(3,corner(6)), &
163  xyz(3,corner(7)),xyz(3,corner(8)))
164  zmax = max(xyz(3,corner(1)),xyz(3,corner(2)),xyz(3,corner(3)), &
165  xyz(3,corner(4)),xyz(3,corner(5)),xyz(3,corner(6)), &
166  xyz(3,corner(7)),xyz(3,corner(8)))
167 
168  IF (xmin < xmn) xmn = xmin
169  IF (xmax > xmx) xmx = xmax
170  IF (ymin < ymn) ymn = ymin
171  IF (ymax > ymx) ymx = ymax
172  IF (zmin < zmn) zmn = zmin
173  IF (zmax > zmx) zmx = zmax
174 
175  IF ((xmin <= global%probeXYZ(iprobe,2)) .AND. &
176  (xmax >= global%probeXYZ(iprobe,2)) .AND. &
177  (ymin <= global%probeXYZ(iprobe,3)) .AND. &
178  (ymax >= global%probeXYZ(iprobe,3)) .AND. &
179  (zmin <= global%probeXYZ(iprobe,4)) .AND. &
180  (zmax >= global%probeXYZ(iprobe,4)) ) THEN
181 
182 ! ----------------- yes; assign block number and cell indices to probePos
183 
184  IF (global%verbLevel >= verbose_med) THEN
185  WRITE(stdout,'(A,1X,A,2(I2,A),3(I2),A)')&
186  solver_name,'Found probe ',iprobe, &
187  ' in block ',ireg,' cell ',i,j,k,&
188  ' with bounding box'
189  WRITE(stdout,'(A,1X,6(E14.5))')&
190  solver_name, xmin, xmax, ymin, ymax,&
191  zmin, zmax
192  ENDIF
193  global%probePos(iprobe,1) = ireg
194  global%probePos(iprobe,2) = i
195  global%probePos(iprobe,3) = j
196  global%probePos(iprobe,4) = k
197 
198 ! ----------------- jump to named loop to stop searching over regions
199 
200  EXIT regs
201  ENDIF
202  ENDDO ! i
203  ENDDO ! j
204  ENDDO ! k
205 
206  ENDIF ! is this region on my proc
207  ENDDO regs ! iReg
208 
209 #ifdef MPI
210 ! ----- must broadcast block with probe to the others. Use
211 ! MAX probePos(iprobe,1); eliminates redundant finds.
212 ! Other do not need the 2:4 elements.
213 
214  CALL mpi_allreduce(global%probePos(iprobe,1),iprobemax,1,mpi_integer, &
215  mpi_max,global%mpiComm,global%mpierr)
216  IF (global%mpierr /= 0) CALL errorstop( global,err_mpi_trouble,__line__ )
217  global%probePos(iprobe,1) = iprobemax
218 #endif
219 
220  ENDIF ! probePOS(iprobe,1) lower than range
221 
222 ! --- check if probe`s region on current processor
223 
224  IF (regions(global%probePos(iprobe,1))%procid==global%myProcid .AND. &
225  regions(global%probePos(iprobe,1))%active==active) THEN
226 
227 ! ----- generate file name
228 
229  WRITE(fname,'(A,I4.4)') trim(global%outDir)//trim(global%casename)//'.prb_',iprobe
230 
231 ! ----- append to existing file (restart) or create new file
232 
233  IF ((global%flowType==flow_unsteady .AND. &
234  global%currentTime>0._rfreal) .OR. &
235  (global%flowType==flow_steady .AND. global%currentIter>1)) THEN
236  INQUIRE(file=fname,exist=fileexists)
237  IF (fileexists) THEN
238  fileappend = .true.
239  IF (global%verbLevel >= verbose_med) THEN
240  print *,solver_name,' Appending to ',trim(fname)
241  ENDIF
242  OPEN(if_probe+iprobe-1,file=fname,form='formatted',status='old', &
243  position='append',iostat=errorflag)
244  ELSE
245  fileappend = .false.
246  IF (global%verbLevel >= verbose_med) THEN
247  print *,solver_name,' Overwriting ',trim(fname)
248  ENDIF
249  OPEN(if_probe+iprobe-1,file=fname,form='formatted', &
250  status='unknown',iostat=errorflag)
251  ENDIF
252  ELSE
253  fileappend = .false.
254  IF (global%verbLevel >= verbose_med) THEN
255  WRITE(stdout,'(A,A,A)')solver_name,' Creating new ',trim(fname)
256  ENDIF
257  OPEN(if_probe+iprobe-1,file=fname,form='formatted',status='unknown', &
258  iostat=errorflag)
259  ENDIF
260  global%error = errorflag
261  IF (global%error /= 0) &
262  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
263 
264 ! ----- write header ...
265 
266  ireg = global%probePos(iprobe,1)
267  ilev = regions(ireg)%currLevel
268  xyz => regions(ireg)%levels(ilev)%grid%xyz
269 
270  CALL rflo_getnodeoffset( regions(ireg),ilev,inoff,ijnoff )
271 
272  i = global%probePos(iprobe,2)
273  j = global%probePos(iprobe,3)
274  k = global%probePos(iprobe,4)
275  corner(1) = indijk(i ,j ,k ,inoff,ijnoff)
276  corner(2) = indijk(i ,j ,k+1,inoff,ijnoff)
277  corner(3) = indijk(i ,j+1,k+1,inoff,ijnoff)
278  corner(4) = indijk(i ,j+1,k ,inoff,ijnoff)
279  corner(5) = indijk(i+1,j ,k ,inoff,ijnoff)
280  corner(6) = indijk(i+1,j ,k+1,inoff,ijnoff)
281  corner(7) = indijk(i+1,j+1,k+1,inoff,ijnoff)
282  corner(8) = indijk(i+1,j+1,k ,inoff,ijnoff)
283 
284  xyzhexa(1:3,1) = xyz(1:3,corner(1))
285  xyzhexa(1:3,2) = xyz(1:3,corner(2))
286  xyzhexa(1:3,3) = xyz(1:3,corner(3))
287  xyzhexa(1:3,4) = xyz(1:3,corner(4))
288  xyzhexa(1:3,5) = xyz(1:3,corner(5))
289  xyzhexa(1:3,6) = xyz(1:3,corner(6))
290  xyzhexa(1:3,7) = xyz(1:3,corner(7))
291  xyzhexa(1:3,8) = xyz(1:3,corner(8))
292 
293  CALL centroidhexa( xyzhexa,xc,yc,zc )
294 
295 ! ----- only if we created a new probe file (not appending to an existing one)
296 
297  IF (.NOT. fileappend) THEN
298  WRITE(if_probe+iprobe-1,1000,iostat=errorflag) &
299  global%probePos(iprobe,1),global%probePos(iprobe,2), &
300  global%probePos(iprobe,3),global%probePos(iprobe,4), &
301  xc,yc,zc
302  global%error = errorflag
303  IF (global%error /= err_none) &
304  CALL errorstop( global,err_file_write,__line__,'File: '//trim(fname) )
305  ELSE
306 
307 ! ----- read the last line to get the last probe dump time. If the initial
308 ! ----- time is earlier, back up to a time prior to the initial one.
309 
310  IF ( global%flowType == flow_unsteady ) THEN
311  probetime = huge(1.0_rfreal)
312  loopunsteady: DO
313  backspace(if_probe+iprobe-1,iostat=errorflag)
314  IF (errorflag /= err_none) EXIT loopunsteady
315  READ (if_probe+iprobe-1,fmt=*,iostat=errorflag) probetime
316  IF (errorflag /= err_none) EXIT loopunsteady
317  IF (floatless(probetime,global%currentTime)) THEN
318  EXIT loopunsteady
319  ELSE
320  backspace(if_probe+iprobe-1,iostat=errorflag)
321  IF (errorflag /= err_none) EXIT loopunsteady
322  ENDIF
323  ENDDO loopunsteady
324  IF (global%verbLevel >= verbose_med) THEN
325  print *,solver_name,' positioned ',trim(fname),' at time ',probetime
326  ENDIF
327  ELSE
328  probeiter = huge(probeiter)
329  loopsteady: DO
330  backspace(if_probe+iprobe-1,iostat=errorflag)
331  IF (errorflag /= err_none) EXIT loopsteady
332  READ (if_probe+iprobe-1,fmt=*,iostat=errorflag) probeiter
333  IF (errorflag /= err_none) EXIT loopsteady
334  IF (probeiter < global%currentIter) THEN
335  EXIT loopsteady
336  ELSE
337  backspace(if_probe+iprobe-1,iostat=errorflag)
338  IF (errorflag /= err_none) EXIT loopsteady
339  ENDIF
340  ENDDO loopsteady
341  ENDIF
342 
343  ENDIF ! Append or new
344 
345  ENDIF ! probe located within region
346 
347  ENDDO ! iprobe
348  ENDIF ! nProbes > 0
349 
350 ! finalize
351 
352  CALL deregisterfunction( global )
353 
354 ! format
355 
356 1000 FORMAT('# probe data (iteration/time, density, u, v, w, p, T)',/, &
357  '# region ',i5,', icell ',i5,', jcell ',i5,', kcell ',i5,/, &
358  '# x=',e13.5,', y=',e13.5,', z=',e13.5)
359 
360 END SUBROUTINE rflo_openprobefile
361 
362 !******************************************************************************
363 !
364 ! RCS Revision history:
365 !
366 ! $Log: RFLO_OpenProbeFile.F90,v $
367 ! Revision 1.7 2008/12/06 08:44:27 mtcampbe
368 ! Updated license.
369 !
370 ! Revision 1.6 2008/11/19 22:17:38 mtcampbe
371 ! Added Illinois Open Source License/Copyright
372 !
373 ! Revision 1.5 2005/06/28 21:58:08 wasistho
374 ! set it back to currentTime
375 !
376 ! Revision 1.4 2005/06/28 08:51:22 rfiedler
377 ! Remove local currentTime; use timeStamp in place of currentTime to open probes.
378 !
379 ! Revision 1.2 2005/02/25 01:50:41 rfiedler
380 ! Probe files now not affected by restarting at an older dump time. Less verbose.
381 !
382 ! Revision 1.1 2004/11/29 20:51:39 wasistho
383 ! lower to upper case
384 !
385 ! Revision 1.14 2004/07/22 21:00:02 wasistho
386 ! fixed missing ifdef MPI around MPI calls
387 !
388 ! Revision 1.13 2004/07/21 21:11:59 wasistho
389 ! allow probes input by coordinates
390 !
391 ! Revision 1.12.2.2 2004/07/02 21:28:37 rfiedler
392 ! Bug fix: use MPI_Allreduce to tell all processes who has the probes. RAF
393 !
394 ! Revision 1.12.2.1 2004/07/02 04:11:25 rfiedler
395 ! Allows Rocflo probes to be specified by coordinates. This routine finds the
396 ! first region containing a cell whose bounding box contains the probe. RAF
397 !
398 ! Revision 1.12 2003/11/20 16:40:40 mdbrandy
399 ! Backing out RocfluidMP changes from 11-17-03
400 !
401 ! Revision 1.8 2003/05/15 02:57:04 jblazek
402 ! Inlined index function.
403 !
404 ! Revision 1.7 2003/02/06 01:22:29 jblazek
405 ! Added check for presence of an old probe file.
406 !
407 ! Revision 1.6 2002/10/12 03:20:50 jblazek
408 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
409 !
410 ! Revision 1.5 2002/09/20 22:22:36 jblazek
411 ! Finalized integration into GenX.
412 !
413 ! Revision 1.4 2002/09/05 17:40:21 jblazek
414 ! Variable global moved into regions().
415 !
416 ! Revision 1.3 2002/06/22 01:13:38 jblazek
417 ! Modified interfaces to BC routines.
418 !
419 ! Revision 1.2 2002/04/03 02:28:52 jblazek
420 ! Added x,y,z location to probe file header.
421 !
422 ! Revision 1.1 2002/02/25 22:36:53 jblazek
423 ! Simplified solver initialization routine.
424 !
425 !******************************************************************************
426 
427 
428 
429 
430 
431 
432 
double ymin() const
double xmax() const
j indices k indices k
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 kpcbeg
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
double xmin() const
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
double zmin() const
**********************************************************************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 jpcbeg
**********************************************************************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 ipcend
subroutine centroidhexa(xyzNodes, cofgX, cofgY, cofgZ)
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
LOGICAL function floatless(a, b)
Definition: ModTools.F90:140
**********************************************************************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 ipcbeg
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 form
double zmax() const
double ymax() const
subroutine rflo_openprobefile(regions)
virtual std::ostream & print(std::ostream &os) const
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
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 jpcend
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_getdimensphys(region, iLev, ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend)