Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_ModInterfacesSolver.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: set explicit interfaces to subroutines and functions.
26 !
27 ! Description: none
28 !
29 ! Notes: none.
30 !
31 !******************************************************************************
32 !
33 ! $Id: RFLO_ModInterfacesSolver.F90,v 1.30 2008/12/06 08:44:16 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2001 by the University of Illinois
36 !
37 !******************************************************************************
38 
40 
41  IMPLICIT NONE
42 
43  INTERFACE
44 
45 ! =============================================================================
46 ! ROCFLO solver
47 ! =============================================================================
48 
49  SUBROUTINE rflo_allocatedatabuffers( regions,iReg )
50  USE moddatastruct, ONLY : t_region
51  TYPE(t_region), POINTER :: regions(:)
52  INTEGER :: ireg
53  END SUBROUTINE rflo_allocatedatabuffers
54 
55  SUBROUTINE rflo_allocatememory( region )
56  USE moddatastruct, ONLY : t_region
57  TYPE(t_region) :: region
58  END SUBROUTINE rflo_allocatememory
59 
60  SUBROUTINE rflo_c2eavgcoeffs( region )
61  USE moddatastruct, ONLY : t_region
62  TYPE(t_region) :: region
63  END SUBROUTINE rflo_c2eavgcoeffs
64 
65  SUBROUTINE rflo_c2eavgcoeffsdegec( region )
66  USE moddatastruct, ONLY : t_region
67  TYPE(t_region) :: region
68  END SUBROUTINE rflo_c2eavgcoeffsdegec
69 
70  SUBROUTINE rflo_c2favgcoeffs( region )
71  USE moddatastruct, ONLY : t_region
72  TYPE(t_region) :: region
73  END SUBROUTINE rflo_c2favgcoeffs
74 
75  SUBROUTINE rflo_c2favgcoeffsdegec( region )
76  USE moddatastruct, ONLY : t_region
77  TYPE(t_region) :: region
78  END SUBROUTINE rflo_c2favgcoeffsdegec
79 
80  SUBROUTINE rflo_c2favgcoeffsdummy( region,patch )
81  USE moddatastruct, ONLY : t_region
82  USE modbndpatch, ONLY : t_patch
83  TYPE(t_region) :: region
84  TYPE(t_patch) :: patch
85  END SUBROUTINE rflo_c2favgcoeffsdummy
86 
87  SUBROUTINE rflo_c2favgcoeffsdummyconn( region,lbound,idir,jdir,kdir, &
88  indbeg,indend,jndbeg,jndend,kndbeg,kndend )
89  USE moddatatypes
90  USE moddatastruct, ONLY : t_region
91  TYPE(t_region) :: region
92  INTEGER :: lbound,idir,jdir,kdir
93  INTEGER :: indbeg, indend, jndbeg, jndend, kndbeg, kndend
94  END SUBROUTINE rflo_c2favgcoeffsdummyconn
95 
96  SUBROUTINE rflo_c2favgcoeffsdummyphys( region,lbound,idir,jdir,kdir, &
97  indbeg,indend,jndbeg,jndend,kndbeg,kndend )
98  USE moddatatypes
99  USE moddatastruct, ONLY : t_region
100  TYPE(t_region) :: region
101  INTEGER :: lbound,idir,jdir,kdir
102  INTEGER :: indbeg, indend, jndbeg, jndend, kndbeg, kndend
103  END SUBROUTINE rflo_c2favgcoeffsdummyphys
104 
105  SUBROUTINE rflo_c2favgcoeffspatch( region,patch )
106  USE moddatastruct, ONLY : t_region
107  USE modbndpatch, ONLY : t_patch
108  TYPE(t_region) :: region
109  TYPE(t_patch) :: patch
110  END SUBROUTINE rflo_c2favgcoeffspatch
111 
112  SUBROUTINE rflo_calccontrolvolumes( region )
113  USE moddatastruct, ONLY : t_region
114  TYPE(t_region) :: region
115  END SUBROUTINE rflo_calccontrolvolumes
116 
117  SUBROUTINE rflo_calcfacevectors( region )
118  USE moddatastruct, ONLY : t_region
119  TYPE(t_region) :: region
120  END SUBROUTINE rflo_calcfacevectors
121 
122  SUBROUTINE rflo_calcforces( region )
123  USE moddatastruct, ONLY : t_region
124  TYPE(t_region) :: region
125  END SUBROUTINE rflo_calcforces
126 
127  SUBROUTINE rflo_calcgridspeeds( region )
128  USE moddatastruct, ONLY : t_region
129  TYPE(t_region) :: region
130  END SUBROUTINE rflo_calcgridspeeds
131 
132  SUBROUTINE rflo_calcmassflow( region )
133  USE moddatastruct, ONLY : t_region
134  TYPE(t_region) :: region
135  END SUBROUTINE rflo_calcmassflow
136 
137  SUBROUTINE rflo_calcthrust( region )
138  USE moddatastruct, ONLY : t_region
139  TYPE(t_region) :: region
140  END SUBROUTINE rflo_calcthrust
141 
142  SUBROUTINE rflo_calctotalmass( region,mass )
143  USE moddatatypes
144  USE moddatastruct, ONLY : t_region
145  REAL(RFREAL) :: mass
146  TYPE(t_region) :: region
147  END SUBROUTINE rflo_calctotalmass
148 
149  SUBROUTINE rflo_centralflux( region )
150  USE moddatastruct, ONLY : t_region
151  TYPE(t_region) :: region
152  END SUBROUTINE rflo_centralflux
153 
154  SUBROUTINE rflo_centralfluxpatch( region,patch )
155  USE moddatastruct, ONLY : t_region
156  USE modbndpatch, ONLY : t_patch
157  TYPE(t_region) :: region
158  TYPE(t_patch) :: patch
159  END SUBROUTINE rflo_centralfluxpatch
160 
161  SUBROUTINE rflo_centraldissipation( region )
162  USE moddatastruct, ONLY : t_region
163  TYPE(t_region) :: region
164  END SUBROUTINE rflo_centraldissipation
165 
166  SUBROUTINE rflo_checkbcinput( regions )
167  USE moddatastruct, ONLY : t_region
168  TYPE(t_region), POINTER :: regions(:)
169  END SUBROUTINE rflo_checkbcinput
170 
171  SUBROUTINE rflo_checkderiveduserinput( regions )
172  USE moddatastruct, ONLY : t_region
173  TYPE(t_region), POINTER :: regions(:)
174  END SUBROUTINE rflo_checkderiveduserinput
175 
176  SUBROUTINE rflo_checkregionfaces( regions )
177  USE moddatastruct, ONLY : t_region
178  TYPE(t_region), POINTER :: regions(:)
179  END SUBROUTINE rflo_checkregionfaces
180 
181  SUBROUTINE rflo_checkmetrics( iReg,region )
182  USE moddatastruct, ONLY : t_region
183  INTEGER :: ireg
184  TYPE(t_region) :: region
185  END SUBROUTINE rflo_checkmetrics
186 
187  SUBROUTINE rflo_checkminimumcells( regions )
188  USE moddatastruct, ONLY : t_region
189  TYPE(t_region), POINTER :: regions(:)
190  END SUBROUTINE rflo_checkminimumcells
191 
192  SUBROUTINE rflo_checkuserinput( regions )
193  USE moddatastruct, ONLY : t_region
194  TYPE(t_region), POINTER :: regions(:)
195  END SUBROUTINE rflo_checkuserinput
196 
197  SUBROUTINE rflo_clearsendrequests( regions,iReg,geometry )
198  USE moddatastruct, ONLY : t_region
199  TYPE(t_region), POINTER :: regions(:)
200  INTEGER :: ireg
201  LOGICAL :: geometry
202  END SUBROUTINE rflo_clearsendrequests
203 
204 #ifndef GENX
205  SUBROUTINE rflo_computeintegralvalues(regions)
206  USE moddatastruct, ONLY: t_region
207  TYPE(t_region), POINTER :: regions(:)
208  END SUBROUTINE rflo_computeintegralvalues
209 #else
210  SUBROUTINE rflo_computeintegralvalues(regions,integ)
211  USE modrocstar ! To access MAN_INTEG_SIZE
212  USE moddatastruct, ONLY: t_region
213  DOUBLE PRECISION, DIMENSION(MAN_INTEG_SIZE) :: integ
214  TYPE(t_region), POINTER :: regions(:)
215  END SUBROUTINE rflo_computeintegralvalues
216 #endif
217 
218  SUBROUTINE rflo_copyboundarydata( global,patchPrev,patch )
219  USE modglobal, ONLY : t_global
220  USE modbndpatch, ONLY : t_patch
221  TYPE(t_global), POINTER :: global
222  TYPE(t_patch), POINTER :: patchprev, patch
223  END SUBROUTINE rflo_copyboundarydata
224 
225  SUBROUTINE rflo_copygeometrydummy( region )
226  USE moddatastruct, ONLY : t_region
227  TYPE(t_region) :: region
228  END SUBROUTINE rflo_copygeometrydummy
229 
230  SUBROUTINE rflo_copytopologylevels( regions )
231  USE moddatastruct, ONLY : t_region
232  TYPE(t_region), POINTER :: regions(:)
233  END SUBROUTINE rflo_copytopologylevels
234 
235  SUBROUTINE rflo_copyvectorcorners( iLev,region,vec )
236  USE moddatatypes
237  USE moddatastruct, ONLY : t_region
238  TYPE(t_region) :: region
239  INTEGER :: ilev
240  REAL(RFREAL), POINTER :: vec(:)
241  END SUBROUTINE rflo_copyvectorcorners
242 
243  SUBROUTINE rflo_copyvectoredges( iLev,region,vec )
244  USE moddatatypes
245  USE moddatastruct, ONLY : t_region
246  TYPE(t_region) :: region
247  INTEGER :: ilev
248  REAL(RFREAL), POINTER :: vec(:)
249  END SUBROUTINE rflo_copyvectoredges
250 
251  SUBROUTINE rflo_copyvectorpatches( iLev,region,vec )
252  USE moddatatypes
253  USE moddatastruct, ONLY : t_region
254  TYPE(t_region) :: region
255  INTEGER :: ilev
256  REAL(RFREAL), POINTER :: vec(:)
257  END SUBROUTINE rflo_copyvectorpatches
258 
259  SUBROUTINE rflo_copymatrixcorners( iLev,region,mat )
260  USE moddatatypes
261  USE moddatastruct, ONLY : t_region
262  TYPE(t_region) :: region
263  INTEGER :: ilev
264  REAL(RFREAL), POINTER :: mat(:,:)
265  END SUBROUTINE rflo_copymatrixcorners
266 
267  SUBROUTINE rflo_copymatrixedges( iLev,region,mat )
268  USE moddatatypes
269  USE moddatastruct, ONLY : t_region
270  TYPE(t_region) :: region
271  INTEGER :: ilev
272  REAL(RFREAL), POINTER :: mat(:,:)
273  END SUBROUTINE rflo_copymatrixedges
274 
275  SUBROUTINE rflo_copymatrixpatches( iLev,region,mat )
276  USE moddatatypes
277  USE moddatastruct, ONLY : t_region
278  TYPE(t_region) :: region
279  INTEGER :: ilev
280  REAL(RFREAL), POINTER :: mat(:,:)
281  END SUBROUTINE rflo_copymatrixpatches
282 
283  SUBROUTINE rflo_correctcorneredgecells( region,patch,bcType )
284  USE modbndpatch, ONLY : t_patch
285  USE moddatastruct, ONLY : t_region
286  INTEGER :: bctype
287  TYPE(t_region) :: region
288  TYPE(t_patch) :: patch
289  END SUBROUTINE rflo_correctcorneredgecells
290 
291  SUBROUTINE rflo_domemoryallocation( regions )
292  USE moddatastruct, ONLY : t_region
293  TYPE (t_region), POINTER :: regions(:)
294  END SUBROUTINE rflo_domemoryallocation
295 
296  SUBROUTINE rflo_dualmultigrid( dTimeSystem,regions )
297  USE moddatatypes
298  USE moddatastruct, ONLY : t_region
299  REAL(RFREAL) :: dtimesystem
300  TYPE (t_region), POINTER :: regions(:)
301  END SUBROUTINE rflo_dualmultigrid
302 
303  SUBROUTINE rflo_dualtimestepping( dTimeSystem,regions )
304  USE moddatatypes
305  USE moddatastruct, ONLY : t_region
306  REAL(RFREAL) :: dtimesystem
307  TYPE (t_region), POINTER :: regions(:)
308  END SUBROUTINE rflo_dualtimestepping
309 
310  SUBROUTINE rflo_dualtstinit( regions,timeLevel )
311  USE moddatastruct, ONLY : t_region
312  INTEGER :: timelevel
313  TYPE(t_region), POINTER :: regions(:)
314  END SUBROUTINE rflo_dualtstinit
315 
316  SUBROUTINE rflo_dualtstpredict( region )
317  USE moddatastruct, ONLY : t_region
318  TYPE(t_region) :: region
319  END SUBROUTINE rflo_dualtstpredict
320 
321  SUBROUTINE rflo_dualtststerm( region )
322  USE moddatastruct, ONLY : t_region
323  TYPE(t_region) :: region
324  END SUBROUTINE rflo_dualtststerm
325 
326  SUBROUTINE rflo_dualtstshift( region )
327  USE moddatastruct, ONLY : t_region
328  TYPE(t_region) :: region
329  END SUBROUTINE rflo_dualtstshift
330 
331  SUBROUTINE rflo_endflowsolver( regions )
332  USE moddatastruct, ONLY : t_region
333  TYPE(t_region), POINTER :: regions(:)
334  END SUBROUTINE rflo_endflowsolver
335 
336  SUBROUTINE rflo_exchangecorneredgecells( regions,iReg )
337  USE moddatastruct, ONLY : t_region
338  TYPE(t_region), POINTER :: regions(:)
339  INTEGER :: ireg
340  END SUBROUTINE rflo_exchangecorneredgecells
341 
342  SUBROUTINE rflo_exchangedummyconf( region,regionSrc,patch,patchSrc )
343  USE modbndpatch, ONLY : t_patch
344  USE moddatastruct, ONLY : t_region
345  TYPE(t_region) :: region, regionsrc
346  TYPE(t_patch) :: patch, patchsrc
347  END SUBROUTINE rflo_exchangedummyconf
348 
349  SUBROUTINE rflo_exchangedummyint( region,regionSrc,patch,patchSrc )
350  USE modbndpatch, ONLY : t_patch
351  USE moddatastruct, ONLY : t_region
352  TYPE(t_region) :: region, regionsrc
353  TYPE(t_patch) :: patch, patchsrc
354  END SUBROUTINE rflo_exchangedummyint
355 
356  SUBROUTINE rflo_exchangedummyireg( region,regionSrc,patch,patchSrc )
357  USE modbndpatch, ONLY : t_patch
358  USE moddatastruct, ONLY : t_region
359  TYPE(t_region) :: region, regionsrc
360  TYPE(t_patch) :: patch, patchsrc
361  END SUBROUTINE rflo_exchangedummyireg
362 
363  SUBROUTINE rflo_exchangegeometry( regions )
364  USE moddatastruct, ONLY : t_region
365  TYPE(t_region), POINTER :: regions(:)
366  END SUBROUTINE rflo_exchangegeometry
367 
368  SUBROUTINE rflo_exchangegeometrycopy( region,regionSrc,patch,patchSrc )
369  USE modbndpatch, ONLY : t_patch
370  USE moddatastruct, ONLY : t_region
371  TYPE(t_region) :: region, regionsrc
372  TYPE(t_patch) :: patch, patchsrc
373  END SUBROUTINE rflo_exchangegeometrycopy
374 
375  SUBROUTINE rflo_exchangegeometrylevels( region,iPatch )
376  USE moddatastruct, ONLY : t_region
377  TYPE(t_region) :: region
378  INTEGER :: ipatch
379  END SUBROUTINE rflo_exchangegeometrylevels
380 
381  SUBROUTINE rflo_exchangegeometryprepare( regions )
382  USE moddatastruct, ONLY : t_region
383  TYPE(t_region), POINTER :: regions(:)
384  END SUBROUTINE rflo_exchangegeometryprepare
385 
386  SUBROUTINE rflo_exchangegeometryrecv( region,regionSrc,patch,patchSrc )
387  USE modbndpatch, ONLY : t_patch
388  USE moddatastruct, ONLY : t_region
389  TYPE(t_region) :: region, regionsrc
390  TYPE(t_patch) :: patch, patchsrc
391  END SUBROUTINE rflo_exchangegeometryrecv
392 
393  SUBROUTINE rflo_exchangegeometrysend( region,regionSrc,patch )
394  USE modbndpatch, ONLY : t_patch
395  USE moddatastruct, ONLY : t_region
396  TYPE(t_region) :: region, regionsrc
397  TYPE(t_patch) :: patch
398  END SUBROUTINE rflo_exchangegeometrysend
399 
400  SUBROUTINE rflo_extrapolategeometry( region )
401  USE moddatastruct, ONLY : t_region
402  TYPE(t_region) :: region
403  END SUBROUTINE rflo_extrapolategeometry
404 
405  SUBROUTINE rflo_findsourcecell( regions,iReg,iLev,ic,jc,kc,icell, &
406  found,rotate,iregsrc )
407  USE moddatastruct, ONLY : t_region
408  INTEGER :: ireg, ilev, ic, jc, kc, icell, iregsrc
409  LOGICAL :: found, rotate
410  TYPE(t_region), POINTER :: regions(:)
411  END SUBROUTINE rflo_findsourcecell
412 
413  SUBROUTINE rflo_findsourcecellinvert( regions,iReg,iLev,ic,jc,kc, &
414  icell,found,rotate,iregsrc )
415  USE moddatastruct, ONLY : t_region
416  INTEGER :: ireg, ilev, ic, jc, kc, icell, iregsrc
417  LOGICAL :: found, rotate
418  TYPE(t_region), POINTER :: regions(:)
419  END SUBROUTINE rflo_findsourcecellinvert
420 
421  SUBROUTINE rflo_sourcecell( region,regionSrc,patch,patchSrc, &
422  ilev, ic,jc,kc,icell,found )
423  USE modbndpatch, ONLY : t_patch
424  USE moddatastruct, ONLY : t_region
425  INTEGER :: ilev, ic, jc, kc, icell
426  LOGICAL :: found
427  TYPE(t_region) :: region, regionsrc
428  TYPE(t_patch), POINTER :: patch, patchsrc
429  END SUBROUTINE rflo_sourcecell
430 
431  SUBROUTINE rflo_findsourceregions( regions )
432  USE moddatastruct, ONLY : t_region
433  TYPE(t_region), POINTER :: regions(:)
434  END SUBROUTINE rflo_findsourceregions
435 
436  SUBROUTINE rflo_findsourcepatches( regions )
437  USE moddatastruct, ONLY : t_region
438  TYPE(t_region), POINTER :: regions(:)
439  END SUBROUTINE rflo_findsourcepatches
440 
441  SUBROUTINE rflo_findthrustpatches( region,iReg )
442  USE moddatastruct, ONLY : t_region
443  INTEGER :: ireg
444  TYPE(t_region) :: region
445  END SUBROUTINE rflo_findthrustpatches
446 
447  SUBROUTINE rflo_initavgcoeffs( region )
448  USE moddatastruct, ONLY : t_region
449  TYPE(t_region) :: region
450  END SUBROUTINE rflo_initavgcoeffs
451 
452 #ifdef GENX
453  SUBROUTINE rflo_initflowsolver( globalGenx,initialTime,communicator, &
454  genxhandle,insurf,invol,obtain_attribute )
455  USE modrocstar, ONLY : t_globalgenx
456  CHARACTER(*), INTENT(in) :: insurf, invol
457  DOUBLE PRECISION, INTENT(in) :: initialtime
458  INTEGER, INTENT(in) :: communicator, genxhandle, obtain_attribute
459  TYPE(t_globalgenx), POINTER :: globalgenx
460  END SUBROUTINE rflo_initflowsolver
461 
462  SUBROUTINE rflo_flowsolver( globalGenx,timeSystem,dTimeSystem,genxHandleBc, &
463  genxhandlegm )
464  USE modrocstar, ONLY : t_globalgenx
465  INTEGER, INTENT(in) :: genxhandlebc, genxhandlegm
466  DOUBLE PRECISION, INTENT(in) :: timesystem, dtimesystem
467  TYPE(t_globalgenx), POINTER :: globalgenx
468  END SUBROUTINE rflo_flowsolver
469 #else
470  SUBROUTINE rflo_initflowsolver( casename,verbLevel,global,regions )
471  USE moddatastruct, ONLY : t_region
472  USE modglobal, ONLY : t_global
473  CHARACTER(*) :: casename
474  INTEGER :: verblevel
475  TYPE(t_global), POINTER :: global
476  TYPE(t_region), POINTER :: regions(:)
477  END SUBROUTINE rflo_initflowsolver
478 
479  SUBROUTINE rflo_flowsolver( dTimeSystem,dIterSystem,regions )
480  USE moddatatypes
481  USE moddatastruct, ONLY : t_region
482  REAL(RFREAL) :: dtimesystem
483  INTEGER :: ditersystem
484  TYPE(t_region), POINTER :: regions(:)
485  END SUBROUTINE rflo_flowsolver
486 #endif
487 
488  SUBROUTINE rflo_getflowsolution( regions )
489  USE moddatastruct, ONLY : t_region
490  TYPE(t_region), POINTER :: regions(:)
491  END SUBROUTINE rflo_getflowsolution
492 
493  SUBROUTINE rflo_getgeometry( regions,iread )
494  USE moddatastruct, ONLY : t_region
495  TYPE(t_region), POINTER :: regions(:)
496  INTEGER :: iread
497  END SUBROUTINE rflo_getgeometry
498 
499  SUBROUTINE rflo_getuserinput( regions )
500  USE moddatastruct, ONLY : t_region
501  TYPE(t_region), POINTER :: regions(:)
502  END SUBROUTINE rflo_getuserinput
503 
504  SUBROUTINE rflo_interpoltofinerlevel( region )
505  USE moddatastruct, ONLY : t_region
506  TYPE(t_region) :: region
507  END SUBROUTINE rflo_interpoltofinerlevel
508 
509  SUBROUTINE rflo_initgridprocedures( regions )
510  USE moddatastruct, ONLY : t_region
511  TYPE(t_region), POINTER :: regions(:)
512  END SUBROUTINE rflo_initgridprocedures
513 
514  SUBROUTINE rflo_limiterreference( regions )
515  USE moddatastruct, ONLY : t_region
516  TYPE(t_region), POINTER :: regions(:)
517  END SUBROUTINE rflo_limiterreference
518 
519  SUBROUTINE rflo_mapregionsprocessors( regions )
520  USE moddatastruct, ONLY : t_region
521  TYPE(t_region), POINTER :: regions(:)
522  END SUBROUTINE rflo_mapregionsprocessors
523 
524  SUBROUTINE rflo_minimumtimestep( regions )
525  USE moddatastruct, ONLY : t_region
526  TYPE(t_region), POINTER :: regions(:)
527  END SUBROUTINE rflo_minimumtimestep
528 
529  SUBROUTINE rflo_mirrorgeometry( region )
530  USE moddatastruct, ONLY : t_region
531  TYPE(t_region) :: region
532  END SUBROUTINE rflo_mirrorgeometry
533 
534  SUBROUTINE rflo_movegridblocks( regions )
535  USE moddatastruct, ONLY : t_region
536  TYPE(t_region), POINTER :: regions(:)
537  END SUBROUTINE rflo_movegridblocks
538 
539  SUBROUTINE rflo_movegridglobal( regions )
540  USE moddatastruct, ONLY : t_region
541  TYPE(t_region), POINTER :: regions(:)
542  END SUBROUTINE rflo_movegridglobal
543 
544  SUBROUTINE rflo_movegridinterfaces( regions )
545  USE moddatastruct, ONLY : t_region
546  TYPE(t_region), POINTER :: regions(:)
547  END SUBROUTINE rflo_movegridinterfaces
548 
549  SUBROUTINE rflo_movegridsurfaces( regions,someMoved )
550  USE moddatastruct, ONLY : t_region
551  LOGICAL :: somemoved
552  TYPE(t_region), POINTER :: regions(:)
553  END SUBROUTINE rflo_movegridsurfaces
554 
555  SUBROUTINE rflo_multigrid( dIterSystem,regions )
556  USE moddatastruct, ONLY : t_region
557  INTEGER :: ditersystem
558  TYPE(t_region), POINTER :: regions(:)
559  END SUBROUTINE rflo_multigrid
560 
561  SUBROUTINE rflo_newgrid( regions )
562  USE moddatastruct, ONLY : t_region
563  TYPE(t_region), POINTER :: regions(:)
564  END SUBROUTINE rflo_newgrid
565 
566  SUBROUTINE rflo_openconverfile( global )
567  USE modglobal, ONLY : t_global
568  TYPE(t_global), POINTER :: global
569  END SUBROUTINE rflo_openconverfile
570 
571  SUBROUTINE rflo_openprobefile( regions )
572  USE moddatastruct, ONLY : t_region
573  TYPE(t_region), POINTER :: regions(:)
574  END SUBROUTINE rflo_openprobefile
575 
576  SUBROUTINE rflo_openthrustfile( global )
577  USE modglobal, ONLY : t_global
578  TYPE(t_global), POINTER :: global
579  END SUBROUTINE rflo_openthrustfile
580 
581  SUBROUTINE rflo_printuserinput( regions )
582  USE moddatastruct, ONLY : t_region
583  TYPE(t_region), POINTER :: regions(:)
584  END SUBROUTINE rflo_printuserinput
585 
586  SUBROUTINE rflo_readbcinputfile( regions )
587  USE moddatastruct, ONLY : t_region
588  TYPE(t_region), POINTER :: regions(:)
589  END SUBROUTINE rflo_readbcinputfile
590 
591  SUBROUTINE rflo_readbcfromfile( global,fname,patch )
592  USE modglobal, ONLY : t_global
593  USE modbndpatch, ONLY : t_patch
594  CHARACTER(*) :: fname
595  TYPE(t_global), POINTER :: global
596  TYPE(t_patch), POINTER :: patch
597  END SUBROUTINE rflo_readbcfromfile
598 
599  SUBROUTINE rflo_readbcfarfsection( regions )
600  USE moddatastruct, ONLY : t_region
601  TYPE(t_region), POINTER :: regions(:)
602  END SUBROUTINE rflo_readbcfarfsection
603 
604  SUBROUTINE rflo_readbcnoslipsection( regions )
605  USE moddatastruct, ONLY : t_region
606  TYPE(t_region), POINTER :: regions(:)
607  END SUBROUTINE rflo_readbcnoslipsection
608 
609  SUBROUTINE rflo_readbcinflowtotangsection( regions )
610  USE moddatastruct, ONLY : t_region
611  TYPE(t_region), POINTER :: regions(:)
612  END SUBROUTINE rflo_readbcinflowtotangsection
613 
614  SUBROUTINE rflo_readbcinflowvelsection( regions,bcTitle )
615  USE moddatastruct, ONLY : t_region
616  TYPE(t_region), POINTER :: regions(:)
617  INTEGER :: bctitle
618  END SUBROUTINE rflo_readbcinflowvelsection
619 
620  SUBROUTINE rflo_readbcinjectmratesection( regions )
621  USE moddatastruct, ONLY : t_region
622  TYPE(t_region), POINTER :: regions(:)
623  END SUBROUTINE rflo_readbcinjectmratesection
624 
625  SUBROUTINE rflo_readbcinjectapnsection( regions )
626  USE moddatastruct, ONLY : t_region
627  TYPE(t_region), POINTER :: regions(:)
628  END SUBROUTINE rflo_readbcinjectapnsection
629 
630  SUBROUTINE rflo_readbcoutflowsection( regions )
631  USE moddatastruct, ONLY : t_region
632  TYPE(t_region), POINTER :: regions(:)
633  END SUBROUTINE rflo_readbcoutflowsection
634 
635  SUBROUTINE rflo_readbcslipwallsection( regions )
636  USE moddatastruct, ONLY : t_region
637  TYPE(t_region), POINTER :: regions(:)
638  END SUBROUTINE rflo_readbcslipwallsection
639 
640  SUBROUTINE rflo_readregionmapsection( global )
641  USE modglobal, ONLY : t_global
642  TYPE(t_global), POINTER :: global
643  END SUBROUTINE rflo_readregionmapsection
644 
645  SUBROUTINE rflo_readtbcinputfile( regions )
646  USE moddatastruct, ONLY : t_region
647  TYPE(t_region), POINTER :: regions(:)
648  END SUBROUTINE rflo_readtbcinputfile
649 
650  SUBROUTINE rflo_readtbcsection( regions,tbcType )
651  USE moddatastruct, ONLY : t_region
652  TYPE(t_region), POINTER :: regions(:)
653  INTEGER, INTENT(IN) :: tbctype
654  END SUBROUTINE rflo_readtbcsection
655 
656  SUBROUTINE rflo_receivecorneredgecells( regions,iReg )
657  USE moddatastruct, ONLY : t_region
658  TYPE(t_region), POINTER :: regions(:)
659  INTEGER :: ireg
660  END SUBROUTINE rflo_receivecorneredgecells
661 
662  SUBROUTINE rflo_receivedummyvals( region,regionSrc,patch,patchSrc )
663  USE modbndpatch, ONLY : t_patch
664  USE moddatastruct, ONLY : t_region
665  TYPE(t_region) :: region, regionsrc
666  TYPE(t_patch) :: patch, patchsrc
667  END SUBROUTINE rflo_receivedummyvals
668 
669  SUBROUTINE rflo_residualnorm( regions )
670  USE moddatastruct, ONLY : t_region
671  TYPE(t_region), POINTER :: regions(:)
672  END SUBROUTINE rflo_residualnorm
673 
674  SUBROUTINE rflo_residualsmoothing( region )
675  USE moddatastruct, ONLY : t_region
676  TYPE(t_region) :: region
677  END SUBROUTINE rflo_residualsmoothing
678 
679  SUBROUTINE rflo_residualsmoothingcoeffs( region )
680  USE moddatastruct, ONLY : t_region
681  TYPE(t_region) :: region
682  END SUBROUTINE rflo_residualsmoothingcoeffs
683 
684  SUBROUTINE rflo_roedissipfirst( region )
685  USE moddatastruct, ONLY : t_region
686  TYPE(t_region) :: region
687  END SUBROUTINE rflo_roedissipfirst
688 
689  SUBROUTINE rflo_roedissipsecond( region )
690  USE moddatastruct, ONLY : t_region
691  TYPE(t_region) :: region
692  END SUBROUTINE rflo_roedissipsecond
693 
694  SUBROUTINE rflo_roefluxfirst( region )
695  USE moddatastruct, ONLY : t_region
696  TYPE(t_region) :: region
697  END SUBROUTINE rflo_roefluxfirst
698 
699  SUBROUTINE rflo_roefluxsecond( region )
700  USE moddatastruct, ONLY : t_region
701  TYPE(t_region) :: region
702  END SUBROUTINE rflo_roefluxsecond
703 
704  SUBROUTINE rflo_roefluxpatch( region,patch )
705  USE moddatastruct, ONLY : t_region
706  USE modbndpatch, ONLY : t_patch
707  TYPE(t_region) :: region
708  TYPE(t_patch) :: patch
709  END SUBROUTINE rflo_roefluxpatch
710 
711  SUBROUTINE rflo_sendcorneredgecells( regions,iReg )
712  USE moddatastruct, ONLY : t_region
713  TYPE(t_region), POINTER :: regions(:)
714  INTEGER :: ireg
715  END SUBROUTINE rflo_sendcorneredgecells
716 
717  SUBROUTINE rflo_senddummyconf( region,regionSrc,patch )
718  USE modbndpatch, ONLY : t_patch
719  USE moddatastruct, ONLY : t_region
720  TYPE(t_region) :: region, regionsrc
721  TYPE(t_patch) :: patch
722  END SUBROUTINE rflo_senddummyconf
723 
724  SUBROUTINE rflo_senddummyint( region,regionSrc,patch )
725  USE modbndpatch, ONLY : t_patch
726  USE moddatastruct, ONLY : t_region
727  TYPE(t_region) :: region, regionsrc
728  TYPE(t_patch) :: patch
729  END SUBROUTINE rflo_senddummyint
730 
731  SUBROUTINE rflo_senddummyireg( region,regionSrc,patch )
732  USE modbndpatch, ONLY : t_patch
733  USE moddatastruct, ONLY : t_region
734  TYPE(t_region) :: region, regionsrc
735  TYPE(t_patch) :: patch
736  END SUBROUTINE rflo_senddummyireg
737 
738  SUBROUTINE rflo_setcorneredgecells( region )
739  USE moddatastruct, ONLY : t_region
740  TYPE(t_region) :: region
741  END SUBROUTINE rflo_setcorneredgecells
742 
743  SUBROUTINE rflo_timestepinviscid( region )
744  USE moddatastruct, ONLY : t_region
745  TYPE(t_region) :: region
746  END SUBROUTINE rflo_timestepinviscid
747 
748  SUBROUTINE rflo_timestepviscous( region )
749  USE moddatastruct, ONLY : t_region
750  TYPE(t_region) :: region
751  END SUBROUTINE rflo_timestepviscous
752 
753  SUBROUTINE rflo_timestepping( dTimeSystem,dIterSystem,regions )
754  USE moddatatypes
755  USE moddatastruct, ONLY : t_region
756  REAL(RFREAL) :: dtimesystem
757  INTEGER :: ditersystem
758  TYPE(t_region), POINTER :: regions(:)
759  END SUBROUTINE rflo_timestepping
760 
761  SUBROUTINE rflo_userinput( regions )
762  USE moddatastruct, ONLY : t_region
763  TYPE(t_region), POINTER :: regions(:)
764  END SUBROUTINE rflo_userinput
765 
766  SUBROUTINE rflo_viscousflux( region,indxMu,indxTCo,tv )
767  USE moddatatypes
768  USE moddatastruct, ONLY : t_region
769  TYPE(t_region) :: region
770  INTEGER :: indxmu, indxtco
771  REAL(RFREAL), POINTER :: tv(:,:)
772  END SUBROUTINE rflo_viscousflux
773 
774  SUBROUTINE rflo_viscousfluxpatch( region,patch,indxMu,indxTCo,tv )
775  USE moddatatypes
776  USE moddatastruct, ONLY : t_region
777  USE modbndpatch, ONLY : t_patch
778  TYPE(t_region) :: region
779  TYPE(t_patch) :: patch
780  INTEGER :: indxmu, indxtco
781  REAL(RFREAL), POINTER :: tv(:,:)
782  END SUBROUTINE rflo_viscousfluxpatch
783 
784  END INTERFACE
785 
786 END MODULE rflo_modinterfacessolver
787 
788 !******************************************************************************
789 !
790 ! RCS Revision history:
791 !
792 ! $Log: RFLO_ModInterfacesSolver.F90,v $
793 ! Revision 1.30 2008/12/06 08:44:16 mtcampbe
794 ! Updated license.
795 !
796 ! Revision 1.29 2008/11/19 22:17:27 mtcampbe
797 ! Added Illinois Open Source License/Copyright
798 !
799 ! Revision 1.28 2006/03/04 04:31:58 wasistho
800 ! moved RFLO_CalcGridMetrics to rocflo module
801 !
802 ! Revision 1.27 2006/01/20 06:14:55 wasistho
803 ! added ReadBcInjectMrate and ReadBcInjectAPN
804 !
805 ! Revision 1.26 2005/11/11 07:16:04 wasistho
806 ! removed RFLO_FindDegeneratCell
807 !
808 ! Revision 1.25 2005/10/20 06:53:41 wasistho
809 ! removed RFLO_CalcCellCentroids from list
810 !
811 ! Revision 1.24 2005/05/28 08:04:13 wasistho
812 ! added RFLO_InitGridProcedures
813 !
814 ! Revision 1.23 2005/05/27 08:09:18 wasistho
815 ! added argument iread in rflo_getgeometry
816 !
817 ! Revision 1.22 2005/04/28 22:04:50 wasistho
818 ! added RFLO_ReadBcInflow...
819 !
820 ! Revision 1.21 2005/03/01 16:36:02 wasistho
821 ! added ModGenx in RFLO_ComputeIntegralValues
822 !
823 ! Revision 1.20 2005/02/26 04:06:25 wasistho
824 ! added RFLO_ComputeIntegralValues
825 !
826 ! Revision 1.19 2004/12/28 22:50:20 wasistho
827 ! moved RFLO_Bcond* and RFLO_BoundaryCond* routines into RFLO_ModBoundaryConditions
828 !
829 ! Revision 1.18 2004/12/02 23:28:02 wasistho
830 ! removed entry BuildVersionString
831 !
832 ! Revision 1.17 2004/11/30 20:10:14 fnajjar
833 ! Included interface for RFLO_CheckDerivedUserInput
834 !
835 ! Revision 1.16 2004/08/25 07:47:35 wasistho
836 ! added RFLO_C2f/eAvgCoeffsDegec and RFLO_InitAvgCoeffs
837 !
838 ! Revision 1.15 2004/08/21 00:35:21 wasistho
839 ! added RFLO_findSourceCellInvert and RFLO_findDegeneratCell
840 !
841 ! Revision 1.14 2004/08/03 22:45:11 wasistho
842 ! added RFLO_c2eAvgCoeffs
843 !
844 ! Revision 1.13 2004/08/02 23:12:27 wasistho
845 ! mv libfloflu/viscousFluxEddy(Patch) to rocflo/RFLO_viscousFlux(Patch)
846 !
847 ! Revision 1.12 2004/07/30 17:28:27 wasistho
848 ! added routines starting RFLO_c2f...
849 !
850 ! Revision 1.11 2004/06/29 23:58:08 wasistho
851 ! migrated to Roccom-3
852 !
853 ! Revision 1.10 2003/10/01 23:52:10 jblazek
854 ! Corrected bug in moving noslip wall BC and grid speeds.
855 !
856 ! Revision 1.9 2003/08/11 21:51:17 jblazek
857 ! Added basic global grid smoothing scheme.
858 !
859 ! Revision 1.8 2003/07/03 21:48:45 jblazek
860 ! Implemented dual-time stepping.
861 !
862 ! Revision 1.7 2003/06/02 17:12:00 jblazek
863 ! Added computation of thrust.
864 !
865 ! Revision 1.6 2003/05/29 17:28:43 jblazek
866 ! Implemented Roe scheme.
867 !
868 ! Revision 1.5 2003/05/20 20:46:57 jblazek
869 ! Values in edge & corner cells now corrected at noslip and symmetry walls.
870 !
871 ! Revision 1.4 2003/02/11 22:52:50 jferry
872 ! Initial import of Rocsmoke
873 !
874 ! Revision 1.3 2003/02/03 19:20:46 jblazek
875 ! Added treatment of edge and corner cells for one processor.
876 !
877 ! Revision 1.2 2003/01/15 22:10:13 jblazek
878 ! Other interfaces to InitFlowSolver and FlowSolver with GENX.
879 !
880 ! Revision 1.1 2002/12/27 22:07:14 jblazek
881 ! Splitted up RFLO_ModInterfaces and ModInterfaces.
882 !
883 !******************************************************************************
884 
885 
886 
887 
888 
889 
subroutine rflo_exchangegeometrycopy(region, regionSrc, patch, patchSrc)
subroutine rflo_c2favgcoeffspatch(region, patch)
**********************************************************************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 kc
subroutine rflo_readbcinjectmratesection(regions)
subroutine rflo_roefluxfirst(region)
subroutine rflo_copygeometrydummy(region)
subroutine rflo_exchangegeometryrecv(region, regionSrc, patch, patchSrc)
subroutine rflo_dualtststerm(region)
subroutine rflo_dualmultigrid(dTimeSystem, regions)
subroutine rflo_readbcoutflowsection(regions)
subroutine rflo_allocatedatabuffers(regions, iReg)
subroutine rflo_openthrustfile(global)
subroutine rflo_readbcslipwallsection(regions)
subroutine rflo_exchangedummyireg(region, regionSrc, patch, patchSrc)
subroutine rflo_exchangegeometrylevels(region, iPatch)
subroutine rflo_setcorneredgecells(region)
subroutine rflo_allocatememory(region)
subroutine rflo_c2favgcoeffsdummyphys(region, lbound, idir, jdir, kdir, indBeg, indEnd, jndBeg, jndEnd, kndBeg, kndEnd)
subroutine rflo_limiterreference(regions)
subroutine rflo_readbcfromfile(global, fname, patch)
subroutine rflo_sendcorneredgecells(regions, iReg)
subroutine rflo_centraldissipation(region)
subroutine rflo_calcforces(region)
subroutine rflo_c2eavgcoeffs(region)
subroutine rflo_residualnorm(regions)
subroutine rflo_extrapolategeometry(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 ic
subroutine rflo_copyvectorpatches(iLev, region, vec)
subroutine rflo_readbcfarfsection(regions)
subroutine rflo_roedissipsecond(region)
subroutine rflo_exchangedummyconf(region, regionSrc, patch, patchSrc)
subroutine rflo_dualtstpredict(region)
subroutine rflo_c2favgcoeffs(region)
subroutine rflo_mapregionsprocessors(regions)
subroutine rflo_getflowsolution(regions)
subroutine rflo_calcmassflow(region)
subroutine rflo_flowsolver(dTimeSystem, dIterSystem, regions)
subroutine rflo_readregionmapsection(global)
subroutine rflo_exchangegeometrysend(region, regionSrc, patch)
subroutine rflo_newgrid(regions)
MPI_Comm communicator() const
Definition: Function.h:119
subroutine rflo_findsourcecellinvert(regions, iReg, iLev, ic, jc, kc, icell, found, rotate, iRegSrc)
subroutine rflo_readbcinputfile(regions)
subroutine rflo_openconverfile(global)
subroutine rflo_readbcinjectapnsection(regions)
subroutine rflo_movegridinterfaces(regions)
subroutine rflo_calccontrolvolumes(region)
subroutine rflo_endflowsolver(regions)
subroutine rflo_copymatrixpatches(iLev, region, mat)
subroutine rflo_exchangecorneredgecells(regions, iReg)
subroutine rflo_receivecorneredgecells(regions, iReg)
subroutine rflo_copytopologylevels(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 jdir
subroutine rflo_receivedummyvals(region, regionSrc, patch, patchSrc)
subroutine rflo_senddummyint(region, regionSrc, patch)
subroutine rflo_timestepping(dTimeSystem, dIterSystem, regions)
Definition: patch.h:74
subroutine rflo_checkderiveduserinput(regions)
subroutine rflo_correctcorneredgecells(region, patch, bcType)
subroutine rflo_calcfacevectors(region)
subroutine rflo_readtbcinputfile(regions)
subroutine rflo_copymatrixcorners(iLev, region, mat)
subroutine rflo_computeintegralvalues(regions)
subroutine rflo_copymatrixedges(iLev, region, mat)
subroutine rflo_printuserinput(regions)
subroutine rflo_c2favgcoeffsdummy(region, patch)
subroutine rflo_exchangegeometry(regions)
subroutine rflo_viscousfluxpatch(region, patch, indxMu, indxTCo, tv)
subroutine rflo_roedissipfirst(region)
subroutine rflo_dualtstshift(region)
subroutine rflo_movegridsurfaces(regions, someMoved)
subroutine rflo_minimumtimestep(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 idir
subroutine rflo_senddummyireg(region, regionSrc, patch)
subroutine rflo_initgridprocedures(regions)
subroutine rflo_checkminimumcells(regions)
subroutine rflo_initavgcoeffs(region)
subroutine rflo_readtbcsection(regions, tbcType)
subroutine rflo_sourcecell(region, regionSrc, patch, patchSrc, iLev, ic, jc, kc, icell, found)
subroutine rflo_multigrid(dIterSystem, regions)
subroutine rflo_initflowsolver(casename, verbLevel, global, regions)
subroutine rflo_residualsmoothing(region)
subroutine rflo_openprobefile(regions)
subroutine rflo_exchangedummyint(region, regionSrc, patch, patchSrc)
subroutine rflo_interpoltofinerlevel(region)
subroutine rflo_findsourceregions(regions)
subroutine rflo_readbcinflowvelsection(regions, bcTitle)
subroutine rflo_dualtstinit(regions, timeLevel)
**********************************************************************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 icell
subroutine rflo_clearsendrequests(regions, iReg, geometry)
subroutine rflo_calcgridspeeds(region)
subroutine rflo_checkbcinput(regions)
subroutine rflo_centralflux(region)
subroutine rflo_findthrustpatches(region, iReg)
subroutine rflo_c2eavgcoeffsdegec(region)
subroutine rflo_findsourcepatches(regions)
subroutine rflo_senddummyconf(region, regionSrc, patch)
subroutine rflo_readbcinflowtotangsection(regions)
subroutine rflo_viscousflux(region, indxMu, indxTCo, tv)
**********************************************************************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 kdir
subroutine rflo_readbcnoslipsection(regions)
void obtain_attribute(const COM::Attribute *attribute_in, COM::Attribute *user_attribute, int *pane_id=NULL)
Fill the destination (second) attribute from files using the data corresponding to the source (first)...
Definition: Rocin.C:2431
subroutine rflo_movegridglobal(regions)
subroutine rflo_findsourcecell(regions, iReg, iLev, ic, jc, kc, icell, found, rotate, iRegSrc)
subroutine rflo_getgeometry(regions, iread)
subroutine rflo_timestepviscous(region)
subroutine rflo_exchangegeometryprepare(regions)
subroutine rflo_copyboundarydata(global, patchPrev, patch)
subroutine rflo_roefluxpatch(region, patch)
subroutine rflo_copyvectorcorners(iLev, region, vec)
subroutine rflo_c2favgcoeffsdegec(region)
subroutine rflo_getuserinput(regions)
subroutine rflo_userinput(regions)
subroutine rflo_dualtimestepping(dTimeSystem, regions)
subroutine rflo_copyvectoredges(iLev, region, vec)
subroutine rflo_checkuserinput(regions)
subroutine rflo_residualsmoothingcoeffs(region)
subroutine rflo_roefluxsecond(region)
subroutine rflo_checkmetrics(iReg, region)
subroutine rflo_calcthrust(region)
subroutine rflo_centralfluxpatch(region, patch)
subroutine rflo_checkregionfaces(regions)
subroutine rflo_calctotalmass(region, mass)
subroutine rflo_c2favgcoeffsdummyconn(region, lbound, idir, jdir, kdir, indBeg, indEnd, jndBeg, jndEnd, kndBeg, kndEnd)
CImg< T > & rotate(const float angle, const unsigned int border_conditions=3, const unsigned int interpolation=1)
Rotate an image.
Definition: CImg.h:17637
subroutine rflo_timestepinviscid(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 jc
subroutine rflo_movegridblocks(regions)
subroutine rflo_domemoryallocation(regions)