Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_WriteSolution.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: write flow solution to file (only mixture for now).
26 !
27 ! Description: the following solution formats are supported:
28 ! - RocfloMP ASCII
29 ! - RocfloMP binary.
30 !
31 ! Input: regions = dimensions and cons. variables of all regions
32 ! global%currentTime = physical time
33 ! global%resInit = initial residual.
34 !
35 ! Output: to file.
36 !
37 ! Notes: solution is stored only for the current grid level; it is also
38 ! stored for all dummy cells. All regions are written into one file.
39 !
40 !******************************************************************************
41 !
42 ! $Id: RFLO_WriteSolution.F90,v 1.3 2008/12/06 08:44:07 mtcampbe Exp $
43 !
44 ! Copyright: (c) 2001 by the University of Illinois
45 !
46 !******************************************************************************
47 
48 SUBROUTINE rflo_writesolution( regions )
49 
50  USE moddatatypes
51  USE moddatastruct, ONLY : t_region
52  USE modglobal, ONLY : t_global
56  USE moderror
57  USE modmpi
58  USE modparameters
59  IMPLICIT NONE
60 
61 #include "Indexing.h"
62 
63 ! ... parameters
64  TYPE(t_region), POINTER :: regions(:)
65 
66 ! ... loop variables
67  INTEGER :: ireg, i, j, k, n
68 
69 ! ... local variables
70  CHARACTER(2*CHRLEN+17) :: fname
71 
72 #ifdef MPI
73  INTEGER :: status(mpi_status_size)
74 #endif
75  INTEGER :: ilev, iregfile, ipc, jpc, kpc, ndumcells, ioff, ijoff, ijk
76  INTEGER :: idcbeg, jdcbeg, kdcbeg, idcend, jdcend, kdcend, ijkbeg, ijkend
77  INTEGER :: ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend, inoff, ijnoff
78  INTEGER :: ndimc, ndimn, nrvar, errorflag
79  INTEGER, ALLOCATABLE :: ivar(:,:)
80 
81  REAL(RFREAL), POINTER :: cv(:,:), sivel(:), sjvel(:), skvel(:)
82  REAL(RFREAL), ALLOCATABLE :: rvar(:,:), cvfile(:,:), svelfile(:,:)
83 
84  TYPE(t_global), POINTER :: global
85 
86 !******************************************************************************
87 
88  global => regions(1)%global
89 
90  CALL registerfunction( global,'RFLO_WriteSolution',&
91  'RFLO_WriteSolution.F90' )
92 
93 ! allocate fixed-size temporary data arrays -----------------------------------
94 
95 #ifdef PERI
96  nrvar = 3
97 #else
98  nrvar = 2
99 #endif
100  ALLOCATE( ivar(5,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 ! open solution file (only master proc.) --------------------------------------
106 
107  IF (global%myProcid == masterproc) THEN
108 
109 ! - unsteady flow
110 
111  IF (global%flowType == flow_unsteady) THEN
112  IF (global%solutFormat == format_ascii) THEN
113  WRITE(fname,'(A,1PE11.5)') trim(global%outDir)//trim(global%casename)//'.sola_', &
114  global%currentTime
115  OPEN(if_solut,file=fname,form='formatted',status='unknown', &
116  iostat=errorflag)
117  ELSE IF (global%solutFormat == format_binary) THEN
118  WRITE(fname,'(A,1PE11.5)') trim(global%outDir)//trim(global%casename)//'.solb_', &
119  global%currentTime
120  OPEN(if_solut,file=fname,form='unformatted',status='unknown', &
121  iostat=errorflag)
122  ELSE
123  CALL errorstop( global,err_unknown_format,__line__ )
124  ENDIF
125  rvar(1,1) = global%currentTime
126  rvar(2,1) = 1._rfreal
127 
128 ! - steady flow
129 
130  ELSE
131  IF (global%solutFormat == format_ascii) THEN
132  WRITE(fname,'(A,I6.6)') trim(global%outDir)//trim(global%casename)//'.sola_', &
133  global%currentIter
134  OPEN(if_solut,file=fname,form='formatted',status='unknown', &
135  iostat=errorflag)
136  ELSE IF (global%solutFormat == format_binary) THEN
137  WRITE(fname,'(A,I6.6)') trim(global%outDir)//trim(global%casename)//'.solb_', &
138  global%currentIter
139  OPEN(if_solut,file=fname,form='unformatted',status='unknown', &
140  iostat=errorflag)
141  ELSE
142  CALL errorstop( global,err_unknown_format,__line__ )
143  ENDIF
144  rvar(1,1) = 0._rfreal
145  rvar(2,1) = global%resInit
146  ENDIF
147 
148 #ifdef PERI
149  rvar(3,1) = global%moduleVar(1)
150 #endif
151 
152  global%error = errorflag
153  IF (global%error /= 0) &
154  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
155 
156  ENDIF ! MASTERPROC
157 
158 ! write time and initial residual to file -------------------------------------
159 
160  IF (global%myProcid == masterproc) THEN
161  CALL rflo_writedatafilereal( global,if_solut,global%solutFormat,nrvar,1,rvar )
162  ENDIF
163 
164 ! write solution data ---------------------------------------------------------
165 
166  DO ireg=1,global%nRegions
167 
168 ! - get dimensions and pointers
169 
170  ilev = regions(ireg)%currLevel
171  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
172  jdcbeg,jdcend,kdcbeg,kdcend )
173  CALL rflo_getcelloffset( regions(ireg),ilev,ioff,ijoff )
174  ijkbeg = indijk(idcbeg,jdcbeg,kdcbeg,ioff,ijoff)
175  ijkend = indijk(idcend,jdcend,kdcend,ioff,ijoff)
176  ndimc = ijkend - ijkbeg + 1
177 
178  CALL rflo_getdimensphysnodes( regions(ireg),ilev,ipnbeg,ipnend, &
179  jpnbeg,jpnend,kpnbeg,kpnend )
180  CALL rflo_getnodeoffset( regions(ireg),ilev,inoff,ijnoff )
181  ndimn = (regions(ireg)%levels(ilev)%grid%ipc+1)* &
182  (regions(ireg)%levels(ilev)%grid%jpc+1)* &
183  (regions(ireg)%levels(ilev)%grid%kpc+1)
184 
185 ! - allocate memory for data field
186 
187  IF (regions(ireg)%procid==global%myProcid .OR. &
188  global%myProcid==masterproc) THEN
189  ALLOCATE( cvfile(cv_mixt_neqs,ndimc),stat=errorflag )
190  global%error = errorflag
191  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
192 
193  IF (regions(ireg)%mixtInput%moveGrid) THEN
194  ALLOCATE( svelfile(3,ndimn),stat=errorflag )
195  global%error = errorflag
196  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
197  ENDIF
198  ENDIF
199 
200 ! - copy solution into data structure
201 
202  IF (regions(ireg)%procid == global%myProcid) THEN
203  cv => regions(ireg)%levels(ilev)%mixt%cv
204  n = 0
205  DO k=kdcbeg,kdcend
206  DO j=jdcbeg,jdcend
207  DO i=idcbeg,idcend
208  n = n + 1
209  ijk = indijk(i,j,k,ioff,ijoff)
210  cvfile(1,n) = cv(cv_mixt_dens,ijk)
211  cvfile(2,n) = cv(cv_mixt_xmom,ijk)
212  cvfile(3,n) = cv(cv_mixt_ymom,ijk)
213  cvfile(4,n) = cv(cv_mixt_zmom,ijk)
214  cvfile(5,n) = cv(cv_mixt_ener,ijk)
215  ENDDO
216  ENDDO
217  ENDDO
218  IF (regions(ireg)%mixtInput%moveGrid) THEN
219  sivel => regions(ireg)%levels(ilev)%grid%siVel
220  sjvel => regions(ireg)%levels(ilev)%grid%sjVel
221  skvel => regions(ireg)%levels(ilev)%grid%skVel
222  n = 0
223  DO k=kpnbeg,kpnend
224  DO j=jpnbeg,jpnend
225  DO i=ipnbeg,ipnend
226  n = n + 1
227  ijk = indijk(i,j,k,inoff,ijnoff)
228  svelfile(1,n) = sivel(ijk)
229  svelfile(2,n) = sjvel(ijk)
230  svelfile(3,n) = skvel(ijk)
231  ENDDO
232  ENDDO
233  ENDDO
234  ENDIF
235  ENDIF ! global%myProcid
236 
237 ! - write region number and dimensions (only master)
238 
239  IF (global%myProcid == masterproc) THEN
240  ivar(1,1) = ireg
241  ivar(2,1) = regions(ireg)%levels(ilev)%grid%ipc
242  ivar(3,1) = regions(ireg)%levels(ilev)%grid%jpc
243  ivar(4,1) = regions(ireg)%levels(ilev)%grid%kpc
244  ivar(5,1) = regions(ireg)%nDumCells
245  CALL rflo_writedatafileint( global,if_solut,global%solutFormat,5,1,ivar )
246  ENDIF
247 
248 ! - master receives and writes data, others send them
249 
250  IF (global%myProcid == masterproc) THEN
251 #ifdef MPI
252  IF (regions(ireg)%procid /= masterproc) THEN
253  CALL mpi_recv( cvfile,cv_mixt_neqs*ndimc,mpi_rfreal, &
254  regions(ireg)%procid,ireg, &
255  global%mpiComm,status,global%mpierr )
256  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
257 
258  IF (regions(ireg)%mixtInput%moveGrid) THEN
259  CALL mpi_recv( svelfile,3*ndimn,mpi_rfreal, &
260  regions(ireg)%procid,ireg, &
261  global%mpiComm,status,global%mpierr )
262  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
263  ENDIF
264  ENDIF
265 #endif
266  CALL rflo_writedatafilereal( global,if_solut,global%solutFormat, &
267  cv_mixt_neqs,ndimc,cvfile )
268 
269  IF (regions(ireg)%mixtInput%moveGrid) THEN
270  CALL rflo_writedatafilereal( global,if_solut,global%solutFormat, &
271  3,ndimn,svelfile )
272  ENDIF
273 
274  ELSE ! not the master
275 #ifdef MPI
276  IF (regions(ireg)%procid == global%myProcid) THEN
277  CALL mpi_send( cvfile,cv_mixt_neqs*ndimc,mpi_rfreal,masterproc,ireg, &
278  global%mpiComm,global%mpierr )
279  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
280 
281  IF (regions(ireg)%mixtInput%moveGrid) THEN
282  CALL mpi_send( svelfile,3*ndimn,mpi_rfreal,masterproc,ireg, &
283  global%mpiComm,global%mpierr )
284  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
285  ENDIF
286  ENDIF
287 #endif
288  ENDIF
289 
290  IF (ALLOCATED(cvfile)) THEN
291  DEALLOCATE( cvfile,stat=errorflag )
292  global%error = errorflag
293  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
294  ENDIF
295  IF (ALLOCATED(svelfile)) THEN
296  DEALLOCATE( svelfile,stat=errorflag )
297  global%error = errorflag
298  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
299  ENDIF
300 
301  ENDDO ! iReg
302 
303 ! finalize --------------------------------------------------------------------
304 
305  IF (global%myProcid == masterproc) THEN
306  CLOSE(if_solut,iostat=errorflag)
307  global%error = errorflag
308  IF (global%error /= 0) &
309  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
310  ENDIF
311 
312  CALL deregisterfunction( global )
313 
314 END SUBROUTINE rflo_writesolution
315 
316 !******************************************************************************
317 !
318 ! RCS Revision history:
319 !
320 ! $Log: RFLO_WriteSolution.F90,v $
321 ! Revision 1.3 2008/12/06 08:44:07 mtcampbe
322 ! Updated license.
323 !
324 ! Revision 1.2 2008/11/19 22:17:21 mtcampbe
325 ! Added Illinois Open Source License/Copyright
326 !
327 ! Revision 1.1 2004/11/29 21:25:17 wasistho
328 ! lower to upper case
329 !
330 ! Revision 1.16 2003/11/20 16:40:35 mdbrandy
331 ! Backing out RocfluidMP changes from 11-17-03
332 !
333 ! Revision 1.13 2003/05/15 02:57:01 jblazek
334 ! Inlined index function.
335 !
336 ! Revision 1.12 2003/04/02 00:24:24 wasistho
337 ! install ROCPERI
338 !
339 ! Revision 1.11 2002/10/23 18:43:24 jblazek
340 ! Changed temporary pointer arrays into allocatable arrays
341 ! in grid and solution I/O routines.
342 !
343 ! Revision 1.10 2002/10/12 03:20:50 jblazek
344 ! Replaced [io]stat=global%error with local errorFlag for Rocflo.
345 !
346 ! Revision 1.9 2002/09/20 22:22:35 jblazek
347 ! Finalized integration into GenX.
348 !
349 ! Revision 1.8 2002/09/05 17:40:19 jblazek
350 ! Variable global moved into regions().
351 !
352 ! Revision 1.7 2002/08/29 21:52:21 jblazek
353 ! Added I/O of grid speeds.
354 !
355 ! Revision 1.6 2002/06/07 16:40:36 jblazek
356 ! Grid & solution for all regions in one file.
357 !
358 ! Revision 1.5 2002/02/21 23:25:05 jblazek
359 ! Blocks renamed as regions.
360 !
361 ! Revision 1.4 2002/02/04 15:30:25 jblazek
362 ! Added injection boundary condition.
363 !
364 ! Revision 1.3 2002/01/08 22:09:16 jblazek
365 ! Added calculation of face vectors and volumes.
366 !
367 ! Revision 1.2 2002/01/02 16:20:19 jblazek
368 ! Added flow initialization and dummy cell geometry.
369 !
370 ! Revision 1.1 2001/12/22 00:09:37 jblazek
371 ! Added routines to store grid and solution.
372 !
373 !******************************************************************************
374 
375 
376 
377 
378 
379 
380 
**********************************************************************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
**********************************************************************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 jpnbeg
subroutine rflo_writedatafileint(global, fileId, form, nDim1, nDim2, ivar)
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 kpnbeg
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
**********************************************************************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 jpnend
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
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
blockLoc i
Definition: read.cpp:79
**********************************************************************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 ipnbeg
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
subroutine rflo_getdimensphysnodes(region, iLev, ipnbeg, ipnend, jpnbeg, jpnend, kpnbeg, kpnend)
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 rflo_writesolution(regions)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine rflo_writedatafilereal(global, fileId, form, nDim1, nDim2, var)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
**********************************************************************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 ipnend