Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
utilities/rocsmoke/post/Main.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 out ROCFLO-MP`s grid and/or solution for visualization,
26 ! with smoke fields included
27 !
28 ! Description: currently supported formats are:
29 ! - TECPLOT Ascii
30 !
31 ! Input: case name from the list of arguments
32 !
33 ! Output: to file.
34 !
35 ! Notes: the output is collected in one file, but the regions are processed
36 ! separately to save memory.
37 !
38 !******************************************************************************
39 !
40 ! $Id: Main.F90,v 1.4 2008/12/06 08:45:08 mtcampbe Exp $
41 !
42 ! Copyright: (c) 2003 by the University of Illinois
43 !
44 !******************************************************************************
45 
47 
48  USE moddatatypes
49  USE moderror
50  USE moddatastruct, ONLY : t_region
51  USE modglobal, ONLY : t_global
52  USE modgrid, ONLY : t_grid
53  USE modmixture, ONLY : t_mixt
54  USE modparteul, ONLY : t_peul
62 #ifdef TURB
65 #endif
66  USE modmpi
67  USE modparameters
68  IMPLICIT NONE
69 
70 #include "Indexing.h"
71 
72 ! ... loop variables
73  INTEGER :: ireg, ilev
74 
75 ! ... local variables
76  CHARACTER(CHRLEN) :: plttype, level, stamp, outfmt, msg, &
77  versionstring, headerstring, npeulstr
78 
79  INTEGER :: plottype, outputformat, npeul
80  INTEGER :: ipc, jpc, kpc, ibc, iec, ibn, ien
81  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend
82  INTEGER :: idnbeg, idnend, jdnbeg, jdnend, kdnbeg, kdnend
83  INTEGER :: icoff, ijcoff, inoff, ijnoff
84  INTEGER :: margin, versionwidth, errorflag
85  INTEGER, PARAMETER :: headerwidth = 53
86 
87  TYPE(t_global), POINTER :: global
88  TYPE(t_region), POINTER :: regions(:)
89  TYPE(t_grid) , POINTER :: grid
90  TYPE(t_mixt) , POINTER :: mixt
91  TYPE(t_peul) , POINTER :: peul
92 
93 !******************************************************************************
94 
95  ALLOCATE( global )
96 
97  global%nFunTree = 0
98  CALL registerfunction( global,'PEUL_ROCFLO_Post', &
99  'Main.F90' )
100 
101 ! initialize global parameters ------------------------------------------------
102 
103  global%verbLevel = verbose_none
104 
105  global%flowType = flow_steady ! stationary flow
106  global%currentTime = -1._rfreal ! no physical time set
107  global%currentIter = -1 ! no iteration
108 
109  global%inDir = './' ! directory path
110  global%outDir = './'
111 
112  global%nProcAlloc = 1
113  global%myProcid = masterproc ! default process number (not an MPI code)
114  global%mpierr = err_none
115  global%error = err_none
116 
117  global%pi = 4._rfreal*atan(1._rfreal)
118  global%rad = global%pi/180._rfreal
119 
120 ! print header ----------------------------------------------------------------
121 
122 #ifdef MPI
123  CALL mpi_init( global%mpierr )
124  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
125 #endif
126 
127  CALL buildversionstring( versionstring )
128 
129  headerstring = ' '
130  versionwidth = len_trim(versionstring)
131  margin = (headerwidth-versionwidth)/2
132  headerstring(margin+1:margin+versionwidth) = versionstring(1:versionwidth)
133  headerstring(1:1) = '*'
134  headerstring(headerwidth:headerwidth) = '*'
135 
136  WRITE(stdout,'(/,A)') solver_name//' *****************************************************'
137  WRITE(stdout, '(A)') solver_name//' * *'
138  WRITE(stdout, '(A)') solver_name//' * ROCSMOKE: Solution Postprocessing *'
139  WRITE(stdout, '(A)') solver_name//' * ================================= *'
140  WRITE(stdout, '(A)') solver_name//' * *'
141  WRITE(stdout, '(A)') solver_name//' '//trim(headerstring)
142  WRITE(stdout, '(A)') solver_name//' * Copyright (c) by the University of Illinois *'
143  WRITE(stdout, '(A)') solver_name//' * *'
144  WRITE(stdout,'(A,/)') solver_name//' *****************************************************'
145 
146 ! read argument list ----------------------------------------------------------
147 
148  CALL getarg(1,global%casename)
149  CALL getarg(2,plttype)
150  CALL getarg(3,level)
151  CALL getarg(4,stamp)
152  CALL getarg(5,outfmt)
153  CALL getarg(6,npeulstr)
154 
155  IF (len_trim(global%casename)==0 .OR. &
156  len_trim(plttype)==0 .OR. &
157  len_trim(level)==0 .OR. &
158  len_trim(stamp)==0 .OR. &
159  len_trim(outfmt)==0 .OR. &
160  len_trim(npeulstr)==0 ) THEN
161  WRITE(stdout,'(/,A,/,A,/,9(A,/))') &
162  solver_name//' Usage: peulpost <casename> <type> <level> <time/iter> <format> <nPeul>', &
163  solver_name, &
164  solver_name//' type = 1 - grid + smoke only', &
165  solver_name//' = 2 - grid + fluid + smoke fields', &
166  solver_name//' ', &
167  solver_name//' level = grid level (>0)', &
168  solver_name//' time/iter = time or iteration number', &
169  solver_name//' ', &
170  solver_name//' format = 3 - Tecplot ASCII', &
171  solver_name//' nPeul = number of smoke fields included'
172 #ifdef MPI
173  CALL mpi_finalize( global%mpierr )
174 #endif
175  stop
176  ENDIF
177 
178  READ(plttype ,*) plottype
179  READ(level ,*) global%startLevel
180  READ(outfmt ,*) outputformat
181  READ(npeulstr,*) npeul
182 
183  IF (plottype <= 1) THEN
184  plottype = plot_grid_only
185  ELSE
186  plottype = plot_grid_flow
187  ENDIF
188 
189  IF (outputformat == 3) THEN
190  outputformat = plot_fmt_tecascii
191  ELSE
192  WRITE(stdout,'(/,A,/)') solver_name// &
193  ' Sorry, binary output not yet supported.'
194 #ifdef MPI
195  CALL mpi_finalize( global%mpierr )
196 #endif
197  stop
198  ENDIF
199 
200 ! read region topology --------------------------------------------------------
201 
202  WRITE(stdout,'(/,A)') solver_name//' Reading region topology ...'
203 
204  CALL rflo_readregiontopology( global,regions )
205 
206  DO ireg=1,global%nRegions
207  regions(ireg)%startLevel = global%startLevel
208  regions(ireg)%currLevel = global%startLevel
209  IF (regions(ireg)%nGridLevels < regions(ireg)%currLevel) THEN
210  WRITE(msg,1000) solver_name,ireg,global%startLevel
211  CALL errorstop( global,err_grid_level,__line__,msg )
212  ENDIF
213  DO ilev=2,regions(ireg)%nGridLevels
214  ipc = regions(ireg)%levels(ilev-1)%grid%ipc
215  jpc = regions(ireg)%levels(ilev-1)%grid%jpc
216  kpc = regions(ireg)%levels(ilev-1)%grid%kpc
217  regions(ireg)%levels(ilev)%grid%ipc = ipc/2
218  regions(ireg)%levels(ilev)%grid%jpc = jpc/2
219  regions(ireg)%levels(ilev)%grid%kpc = kpc/2
220  ENDDO
221  ENDDO
222 
223 ! get user parameters ---------------------------------------------------------
224 
225  WRITE(stdout,'(/,A)') solver_name//' Reading user input ...'
226 
227  CALL rflo_initinputvalues( regions )
228  CALL readinputfile( regions )
229  CALL rflo_derivedinputvalues( regions )
230 #ifdef TURB
231  CALL turb_readinputfile( regions )
232  CALL turb_derivedinputvalues( regions )
233 #endif
234 
235  IF (global%flowType == flow_steady) THEN
236  READ(stamp,*) global%currentIter
237  ELSE
238  READ(stamp,*) global%timeStamp
239  global%currentTime = global%timeStamp
240  ENDIF
241 
242 ! loop over regions -----------------------------------------------------------
243 
244  IF (plottype == plot_grid_only) THEN
245  WRITE(stdout,'(A)') solver_name// &
246  ' Reading grid + smoke and writing plot file ...'
247  ELSE
248  WRITE(stdout,'(A)') solver_name// &
249  ' Reading grid + fluid + smoke and writing plot file ...'
250  ENDIF
251 
252  DO ireg=1,global%nRegions
253 
254  WRITE(stdout,'(A,I5.5)') solver_name//' - region ',ireg
255 
256 ! - allocate memory for the grid (all grid levels)
257 
258  DO ilev=1,regions(ireg)%nGridLevels
259  CALL rflo_getdimensdummynodes( regions(ireg),ilev,idnbeg,idnend, &
260  jdnbeg,jdnend,kdnbeg,kdnend )
261  CALL rflo_getnodeoffset( regions(ireg),ilev,inoff,ijnoff )
262  ibn = indijk(idnbeg,jdnbeg,kdnbeg,inoff,ijnoff)
263  ien = indijk(idnend,jdnend,kdnend,inoff,ijnoff)
264  grid => regions(ireg)%levels(ilev)%grid
265  ALLOCATE( grid%xyz(3,ibn:ien),stat=errorflag )
266  global%error = errorflag
267  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
268  ENDDO
269 
270 ! - allocate memory for the rest (current grid level)
271 
272  ilev = regions(ireg)%currLevel
273  grid => regions(ireg)%levels(ilev)%grid
274  mixt => regions(ireg)%levels(ilev)%mixt
275  peul => regions(ireg)%levels(ilev)%peul
276 
277  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
278  jdcbeg,jdcend,kdcbeg,kdcend )
279  CALL rflo_getcelloffset( regions(ireg),ilev,icoff,ijcoff )
280  ibc = indijk(idcbeg,jdcbeg,kdcbeg,icoff,ijcoff)
281  iec = indijk(idcend,jdcend,kdcend,icoff,ijcoff)
282 
283  CALL rflo_getdimensdummynodes( regions(ireg),ilev,idnbeg,idnend, &
284  jdnbeg,jdnend,kdnbeg,kdnend )
285  CALL rflo_getnodeoffset( regions(ireg),ilev,inoff,ijnoff )
286  ibn = indijk(idnbeg,jdnbeg,kdnbeg,inoff,ijnoff)
287  ien = indijk(idnend,jdnend,kdnend,inoff,ijnoff)
288 
289  IF (regions(ireg)%mixtInput%moveGrid) THEN
290  ALLOCATE( grid%siVel(ibn:ien),stat=errorflag )
291  ALLOCATE( grid%sjVel(ibn:ien),stat=errorflag )
292  ALLOCATE( grid%skVel(ibn:ien),stat=errorflag )
293  ENDIF
294  global%error = errorflag
295  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
296 
297  IF (plottype == plot_grid_flow) THEN
298  ALLOCATE( mixt%cv(5,ibc:iec),stat=errorflag )
299  ALLOCATE( mixt%dv(mixt%nDv,ibc:iec),stat=errorflag )
300  IF (regions(ireg)%mixtInput%computeTv) THEN
301  ALLOCATE( mixt%tv(mixt%nTv,ibc:iec),stat=errorflag )
302  ENDIF
303  IF (regions(ireg)%mixtInput%gasModel == gas_model_tcperf) THEN
304  ALLOCATE( mixt%gv(mixt%nGv,0:1),stat=errorflag )
305  ELSE
306  ALLOCATE( mixt%gv(mixt%nGv,ibc:iec),stat=errorflag )
307  ENDIF
308  ENDIF
309 
310  peul%nCv = npeul
311  regions(ireg)%peulInput%nPtypes = npeul
312  IF (npeul > 0) THEN
313  ALLOCATE( peul%cv(npeul,ibc:iec),stat=errorflag )
314  ENDIF
315 
316  global%error = errorflag
317  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
318 
319 ! - read grid
320 
321  CALL rflo_readgridregion( ireg,regions )
322  CALL rflo_generatecoarsegrids( regions(ireg) )
323  CALL rflo_copygeometrydummy( regions(ireg) )
324 
325 ! - read solution, calc. mixture properties
326 
327  IF (plottype == plot_grid_flow) THEN
328  CALL rflo_readsolutionregion( ireg,regions )
329  CALL mixtureproperties( regions(ireg),ibc,iec,.true. )
330  ENDIF
331 
332 ! - read smoke solution
333 
334  IF (npeul > 0) THEN
335  WRITE(*,*) ' Entering PEUL_ReadSolutionRegion: iReg = ', ireg
336  CALL peul_readsolutionregion( ireg,regions )
337  WRITE(*,*) ' Exiting PEUL_ReadSolutionRegion: iReg = ', ireg
338  ENDIF
339 
340  IF (outputformat == plot_fmt_tecascii) THEN
341 
342 ! --- write data to TECPLOT file (ASCII)
343 
344  CALL writetecplotascii( ireg,ilev,plottype,regions(ireg) )
345 
346  ENDIF
347 
348 ! - deallocate memory
349 
350  DO ilev=1,regions(ireg)%nGridLevels
351  grid => regions(ireg)%levels(ilev)%grid
352  DEALLOCATE( grid%xyz,stat=errorflag )
353  global%error = errorflag
354  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
355  ENDDO
356 
357  ilev = regions(ireg)%currLevel
358  IF (regions(ireg)%mixtInput%moveGrid) THEN
359  grid => regions(ireg)%levels(ilev)%grid
360  DEALLOCATE( grid%siVel,stat=errorflag )
361  DEALLOCATE( grid%sjVel,stat=errorflag )
362  DEALLOCATE( grid%skVel,stat=errorflag )
363  ENDIF
364  IF (plottype == plot_grid_flow) THEN
365  DEALLOCATE( mixt%cv ,stat=errorflag )
366  DEALLOCATE( mixt%dv ,stat=errorflag )
367  DEALLOCATE( mixt%tv ,stat=errorflag )
368  DEALLOCATE( mixt%gv ,stat=errorflag )
369  ENDIF
370  IF (npeul > 0) DEALLOCATE( peul%cv ,stat=errorflag )
371  global%error = errorflag
372  IF (global%error /= 0) CALL errorstop( global,err_deallocate,__line__ )
373 
374  ENDDO ! iReg
375 
376 ! finalize --------------------------------------------------------------------
377 
378  CALL deregisterfunction( global )
379 
380  WRITE(stdout,'(/,A)') solver_name//' Finished.'
381 
382 #ifdef MPI
383  CALL mpi_finalize( global%mpierr )
384 #endif
385 
386 1000 FORMAT(a,' Region ',i5,', grid level= ',i2,'.')
387 
388 END PROGRAM peul_rocflo_post
389 
390 !******************************************************************************
391 !
392 ! RCS Revision history:
393 !
394 ! $Log: Main.F90,v $
395 ! Revision 1.4 2008/12/06 08:45:08 mtcampbe
396 ! Updated license.
397 !
398 ! Revision 1.3 2008/11/19 22:18:18 mtcampbe
399 ! Added Illinois Open Source License/Copyright
400 !
401 ! Revision 1.2 2005/10/31 21:09:39 haselbac
402 ! Changed specModel and SPEC_MODEL_NONE
403 !
404 ! Revision 1.1 2004/12/01 22:29:09 fnajjar
405 ! Initial revision after changing case
406 !
407 ! Revision 1.3 2004/03/03 23:55:42 jferry
408 ! Allowed particles to be run with Euler case
409 !
410 ! Revision 1.2 2003/09/26 22:51:04 jferry
411 ! changed header printed out
412 !
413 ! Revision 1.1 2003/09/25 15:40:22 jferry
414 ! Implented Rocsmoke post-processing
415 !
416 !
417 !******************************************************************************
418 
419 
420 
421 
422 
423 
424 
subroutine turb_derivedinputvalues(regions)
subroutine rflo_copygeometrydummy(region)
**********************************************************************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
program peul_rocflo_post
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine rflo_readsolutionregion(iReg, regions)
**********************************************************************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 jdnbeg
**********************************************************************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 idnend
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
**********************************************************************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 jdnend
subroutine rflo_readgridregion(iReg, regions)
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 idnbeg
subroutine buildversionstring(versionString)
**********************************************************************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 writetecplotascii(iReg, region)
subroutine peul_readsolutionregion(iReg, regions)
subroutine rflo_generatecoarsegrids(region)
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
subroutine readinputfile(regions)
subroutine rflo_derivedinputvalues(regions)
**********************************************************************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
**********************************************************************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_getdimensdummynodes(region, iLev, idnbeg, idnend, jdnbeg, jdnend, kdnbeg, kdnend)
subroutine rflo_readregiontopology(global, regions)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine mixtureproperties(region, inBeg, inEnd, gasUpdate)
subroutine grid(bp)
Definition: setup_py.f90:257
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine turb_readinputfile(regions)
subroutine rflo_initinputvalues(regions)
**********************************************************************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 kdnbeg
RT a() const
Definition: Line_2.h:140