Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLO_DualTstUtil.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: utility functions for the dual time-steping.
26 !
27 ! Description: file contains the following subroutines:
28 !
29 ! - DualTstInit = initialize flow solutions at all time levels
30 ! - DualTstPredict = guess start solution for subiterations
31 ! - DualTstSterm = compute the source term
32 ! - DualTstShift = shift time levels.
33 !
34 ! Input: region = current region
35 ! regions = all regions
36 ! timeLevel = time level of conserved variables to be stored (0-2).
37 !
38 ! Output: region(s) = updated values for region(s).
39 !
40 ! Notes: none.
41 !
42 !******************************************************************************
43 !
44 ! $Id: RFLO_DualTstUtil.F90,v 1.6 2008/12/06 08:44:26 mtcampbe Exp $
45 !
46 ! Copyright: (c) 2003 by the University of Illinois
47 !
48 !******************************************************************************
49 
50 SUBROUTINE rflo_dualtstinit( regions,timeLevel )
51 
52  USE moddatatypes
53  USE modglobal, ONLY : t_global
54  USE moddatastruct, ONLY : t_region
56  USE moderror
57  USE modparameters
58 #ifdef TURB
60 #endif
61  IMPLICIT NONE
62 
63 #include "Indexing.h"
64 
65 ! ... parameters
66  INTEGER :: timelevel
67 
68  TYPE(t_region), POINTER :: regions(:)
69 
70 ! ... loop variables
71  INTEGER :: ireg, ic, id
72 
73 ! ... local variables
74  INTEGER :: ilev, ibc, iec
75  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend, icoff, ijcoff
76 
77  REAL(RFREAL), POINTER :: cv(:,:), cvn(:,:)
78 
79  TYPE(t_global), POINTER :: global
80 
81 #ifdef TURB
82  LOGICAL :: turbused
83 #endif
84 
85 !******************************************************************************
86 
87  global => regions(1)%global
88 
89  CALL registerfunction( global,'RFLO_DualTstInit',&
90  'RFLO_DualTstUtil.F90' )
91 
92  DO ireg=1,global%nRegions
93  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
94  regions(ireg)%active==active) THEN ! on my processor
95 
96  ilev = regions(ireg)%currLevel
97  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
98  jdcbeg,jdcend,kdcbeg,kdcend )
99  CALL rflo_getcelloffset( regions(ireg),ilev,icoff,ijcoff )
100  ibc = indijk(idcbeg,jdcbeg,kdcbeg,icoff,ijcoff)
101  iec = indijk(idcend,jdcend,kdcend,icoff,ijcoff)
102 
103  cv => regions(ireg)%levels(ilev)%mixt%cv
104  IF (timelevel == 0) THEN
105  cvn => regions(ireg)%levels(ilev)%mixt%cvn
106  ELSE IF (timelevel == 1) THEN
107  cvn => regions(ireg)%levels(ilev)%mixt%cvn1
108  ELSE
109  cvn => regions(ireg)%levels(ilev)%mixt%cvn2
110  ENDIF
111 
112  DO ic=ibc,iec
113  cvn(cv_mixt_dens,ic) = cv(cv_mixt_dens,ic)
114  cvn(cv_mixt_xmom,ic) = cv(cv_mixt_xmom,ic)
115  cvn(cv_mixt_ymom,ic) = cv(cv_mixt_ymom,ic)
116  cvn(cv_mixt_zmom,ic) = cv(cv_mixt_zmom,ic)
117  cvn(cv_mixt_ener,ic) = cv(cv_mixt_ener,ic)
118  ENDDO
119 
120 ! --- turbulence part --------------------------------------------------------
121 
122 #ifdef TURB
123  turbused = (regions(ireg)%mixtInput%flowModel == flow_navst .AND. &
124  regions(ireg)%mixtInput%turbModel /= turb_model_none)
125 
126  IF (turbused) THEN
127  IF (regions(ireg)%turbInput%modelClass == model_rans .AND. &
128  regions(ireg)%turbInput%nCv > 0) THEN
129 
130  cv => regions(ireg)%levels(ilev)%turb%cv
131  IF (timelevel == 0) THEN
132  cvn => regions(ireg)%levels(ilev)%turb%cvn
133  ELSE IF (timelevel == 1) THEN
134  cvn => regions(ireg)%levels(ilev)%turb%cvn1
135  ELSE
136  cvn => regions(ireg)%levels(ilev)%turb%cvn2
137  ENDIF
138 
139  DO ic=ibc,iec
140  DO id=1,regions(ireg)%turbInput%nCv
141  cvn(id,ic) = cv(id,ic)
142  ENDDO
143  ENDDO
144  ENDIF ! rans
145  ENDIF ! turbused
146 #endif
147 
148  ENDIF ! region on this processor and active
149  ENDDO ! iReg
150 
151  CALL deregisterfunction( global )
152 
153 END SUBROUTINE rflo_dualtstinit
154 
155 ! #############################################################################
156 ! #############################################################################
157 
158 SUBROUTINE rflo_dualtstpredict( region )
159 
160  USE moddatatypes
161  USE modglobal, ONLY : t_global
162  USE moddatastruct, ONLY : t_region
165  USE moderror
166  USE modparameters
167 #ifdef TURB
169 #endif
170  IMPLICIT NONE
171 
172 #include "Indexing.h"
173 
174 ! ... parameters
175  TYPE(t_region) :: region
176 
177 ! ... loop variables
178  INTEGER :: i, j, k, ic, id
179 
180 ! ... local variables
181  INTEGER :: ilev, ibc, iec
182  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend, icoff, ijcoff
183  INTEGER :: ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend
184 
185  REAL(RFREAL), POINTER :: cv(:,:), cvn(:,:), cvn1(:,:), cvn2(:,:)
186 
187  TYPE(t_global), POINTER :: global
188 
189 #ifdef TURB
190  LOGICAL :: turbused
191 #endif
192 
193 !******************************************************************************
194 
195  global => region%global
196 
197  CALL registerfunction( global,'RFLO_DualTstPredict',&
198  'RFLO_DualTstUtil.F90' )
199 
200  ilev = region%currLevel
201  CALL rflo_getdimensdummy( region,ilev,idcbeg,idcend, &
202  jdcbeg,jdcend,kdcbeg,kdcend )
203  CALL rflo_getdimensphys( region,ilev,ipcbeg,ipcend, &
204  jpcbeg,jpcend,kpcbeg,kpcend )
205  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
206  ibc = indijk(idcbeg,jdcbeg,kdcbeg,icoff,ijcoff)
207  iec = indijk(idcend,jdcend,kdcend,icoff,ijcoff)
208 
209  cv => region%levels(ilev)%mixt%cv
210  cvn => region%levels(ilev)%mixt%cvn
211  cvn1 => region%levels(ilev)%mixt%cvn1
212  cvn2 => region%levels(ilev)%mixt%cvn2
213 
214 ! cv(pseudo) = cv(n) + (3cv(n) - 4cv(n-1) + cv(n-2))/2 -----------------------
215 
216  DO k=kpcbeg,kpcend
217  DO j=jpcbeg,jpcend
218  DO i=ipcbeg,ipcend
219  ic = indijk(i,j,k,icoff,ijcoff)
220  cv(cv_mixt_dens,ic) = cvn(cv_mixt_dens,ic) + &
221  0.5_rfreal*(3._rfreal*cvn(cv_mixt_dens,ic)-&
222  4._rfreal*cvn1(cv_mixt_dens,ic)+&
223  cvn2(cv_mixt_dens,ic))
224  cv(cv_mixt_xmom,ic) = cvn(cv_mixt_xmom,ic) + &
225  0.5_rfreal*(3._rfreal*cvn(cv_mixt_xmom,ic)-&
226  4._rfreal*cvn1(cv_mixt_xmom,ic)+&
227  cvn2(cv_mixt_xmom,ic))
228  cv(cv_mixt_ymom,ic) = cvn(cv_mixt_ymom,ic) + &
229  0.5_rfreal*(3._rfreal*cvn(cv_mixt_ymom,ic)-&
230  4._rfreal*cvn1(cv_mixt_ymom,ic)+&
231  cvn2(cv_mixt_ymom,ic))
232  cv(cv_mixt_zmom,ic) = cvn(cv_mixt_zmom,ic) + &
233  0.5_rfreal*(3._rfreal*cvn(cv_mixt_zmom,ic)-&
234  4._rfreal*cvn1(cv_mixt_zmom,ic)+&
235  cvn2(cv_mixt_zmom,ic))
236  cv(cv_mixt_ener,ic) = cvn(cv_mixt_ener,ic) + &
237  0.5_rfreal*(3._rfreal*cvn(cv_mixt_ener,ic)-&
238  4._rfreal*cvn1(cv_mixt_ener,ic)+&
239  cvn2(cv_mixt_ener,ic))
240  ENDDO
241  ENDDO
242  ENDDO
243 
244  IF (region%mixtInput%gasModel == gas_model_tcperf) THEN
245  CALL mixtureproperties( region,ibc,iec,.false. )
246  ELSE
247  CALL mixtureproperties( region,ibc,iec,.true. )
248  ENDIF
249 
250 ! turbulence part ------------------------------------------------------------
251 
252 #ifdef TURB
253  turbused = (region%mixtInput%flowModel == flow_navst .AND. &
254  region%mixtInput%turbModel /= turb_model_none)
255 
256  IF (turbused) THEN
257  IF (region%turbInput%modelClass == model_rans .AND. &
258  region%turbInput%nCv > 0) THEN
259 
260  cv => region%levels(ilev)%turb%cv
261  cvn => region%levels(ilev)%turb%cvn
262  cvn1 => region%levels(ilev)%turb%cvn1
263  cvn2 => region%levels(ilev)%turb%cvn2
264 
265  DO k=kpcbeg,kpcend
266  DO j=jpcbeg,jpcend
267  DO i=ipcbeg,ipcend
268  ic = indijk(i,j,k,icoff,ijcoff)
269 
270  DO id=1,region%turbInput%nCv
271  cv(id,ic) = cvn(id,ic) + &
272  0.5_rfreal*(3._rfreal*cvn(id,ic)-&
273  4._rfreal*cvn1(id,ic)+&
274  cvn2(id,ic))
275  ENDDO ! id
276  ENDDO
277  ENDDO
278  ENDDO
279  ENDIF ! rans
280  ENDIF ! turbused
281 #endif
282 
283  CALL deregisterfunction( global )
284 
285 END SUBROUTINE rflo_dualtstpredict
286 
287 ! #############################################################################
288 ! #############################################################################
289 
290 SUBROUTINE rflo_dualtststerm( region )
291 
292  USE moddatatypes
293  USE modglobal, ONLY : t_global
294  USE moddatastruct, ONLY : t_region
296  USE moderror
297  USE modparameters
298 #ifdef TURB
300 #endif
301  IMPLICIT NONE
302 
303 #include "Indexing.h"
304 
305 ! ... parameters
306  TYPE(t_region) :: region
307 
308 ! ... loop variables
309  INTEGER :: ic, id
310 
311 ! ... local variables
312  INTEGER :: ilev, ibc, iec
313  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend, icoff, ijcoff
314 
315  REAL(RFREAL) :: rdt2, rdt5
316  REAL(RFREAL), POINTER :: cvn(:,:), cvn1(:,:), sdual(:,:)
317  REAL(RFREAL), POINTER :: vol(:), volold(:)
318 
319  TYPE(t_global), POINTER :: global
320 
321 #ifdef TURB
322  LOGICAL :: turbused
323 #endif
324 
325 !******************************************************************************
326 
327  global => region%global
328 
329  CALL registerfunction( global,'RFLO_DualTstSterm',&
330  'RFLO_DualTstUtil.F90' )
331 
332  ilev = region%currLevel
333  CALL rflo_getdimensdummy( region,ilev,idcbeg,idcend, &
334  jdcbeg,jdcend,kdcbeg,kdcend )
335  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
336  ibc = indijk(idcbeg,jdcbeg,kdcbeg,icoff,ijcoff)
337  iec = indijk(idcend,jdcend,kdcend,icoff,ijcoff)
338 
339  cvn => region%levels(ilev)%mixt%cvn
340  cvn1 => region%levels(ilev)%mixt%cvn1
341  sdual => region%levels(ilev)%mixt%sDual
342  vol => region%levels(ilev)%grid%vol
343  rdt2 = 2._rfreal/global%dtMin
344  rdt5 = 0.5_rfreal/global%dtMin
345 
346 ! compute dual tst source term Q* --------------------------------------------
347 
348  IF (region%mixtInput%moveGrid) THEN
349  volold => region%levels(ilev)%gridOld%vol
350  DO ic=ibc,iec
351  sdual(cv_mixt_dens,ic) = rdt2*vol(ic) *cvn(cv_mixt_dens,ic) - &
352  rdt5*volold(ic)*cvn1(cv_mixt_dens,ic)
353  sdual(cv_mixt_xmom,ic) = rdt2*vol(ic) *cvn(cv_mixt_xmom,ic) - &
354  rdt5*volold(ic)*cvn1(cv_mixt_xmom,ic)
355  sdual(cv_mixt_ymom,ic) = rdt2*vol(ic) *cvn(cv_mixt_ymom,ic) - &
356  rdt5*volold(ic)*cvn1(cv_mixt_ymom,ic)
357  sdual(cv_mixt_zmom,ic) = rdt2*vol(ic) *cvn(cv_mixt_zmom,ic) - &
358  rdt5*volold(ic)*cvn1(cv_mixt_zmom,ic)
359  sdual(cv_mixt_ener,ic) = rdt2*vol(ic) *cvn(cv_mixt_ener,ic) - &
360  rdt5*volold(ic)*cvn1(cv_mixt_ener,ic)
361  ENDDO
362  ELSE
363  DO ic=ibc,iec
364  sdual(cv_mixt_dens,ic) = vol(ic)*(rdt2*cvn(cv_mixt_dens,ic)- &
365  rdt5*cvn1(cv_mixt_dens,ic))
366  sdual(cv_mixt_xmom,ic) = vol(ic)*(rdt2*cvn(cv_mixt_xmom,ic)- &
367  rdt5*cvn1(cv_mixt_xmom,ic))
368  sdual(cv_mixt_ymom,ic) = vol(ic)*(rdt2*cvn(cv_mixt_ymom,ic)- &
369  rdt5*cvn1(cv_mixt_ymom,ic))
370  sdual(cv_mixt_zmom,ic) = vol(ic)*(rdt2*cvn(cv_mixt_zmom,ic)- &
371  rdt5*cvn1(cv_mixt_zmom,ic))
372  sdual(cv_mixt_ener,ic) = vol(ic)*(rdt2*cvn(cv_mixt_ener,ic)- &
373  rdt5*cvn1(cv_mixt_ener,ic))
374  ENDDO
375  ENDIF
376 
377 ! turbulence part ------------------------------------------------------------
378 
379 #ifdef TURB
380  turbused = (region%mixtInput%flowModel == flow_navst .AND. &
381  region%mixtInput%turbModel /= turb_model_none)
382 
383  IF (turbused) THEN
384  IF (region%turbInput%modelClass == model_rans .AND. &
385  region%turbInput%nCv > 0) THEN
386 
387  cvn => region%levels(ilev)%turb%cvn
388  cvn1 => region%levels(ilev)%turb%cvn1
389  sdual => region%levels(ilev)%turb%sDual
390 
391  IF (region%mixtInput%moveGrid) THEN
392  volold => region%levels(ilev)%gridOld%vol
393  DO ic=ibc,iec
394  DO id=1,region%turbInput%nCv
395  sdual(id,ic) = rdt2*vol(ic)*cvn(id,ic) - &
396  rdt5*volold(ic)*cvn1(id,ic)
397  ENDDO
398  ENDDO
399  ELSE
400  DO ic=ibc,iec
401  DO id=1,region%turbInput%nCv
402  sdual(id,ic) = vol(ic)*(rdt2*cvn(id,ic)- &
403  rdt5*cvn1(id,ic))
404  ENDDO
405  ENDDO
406  ENDIF ! movegrid
407  ENDIF ! rans
408  ENDIF ! turbused
409 #endif
410 
411  CALL deregisterfunction( global )
412 
413 END SUBROUTINE rflo_dualtststerm
414 
415 ! #############################################################################
416 ! #############################################################################
417 
418 SUBROUTINE rflo_dualtstshift( region )
419 
420  USE moddatatypes
421  USE modglobal, ONLY : t_global
422  USE moddatastruct, ONLY : t_region
424  USE moderror
425  USE modparameters
426 #ifdef TURB
428 #endif
429  IMPLICIT NONE
430 
431 #include "Indexing.h"
432 
433 ! ... parameters
434  TYPE(t_region) :: region
435 
436 ! ... loop variables
437  INTEGER :: ic, id
438 
439 ! ... local variables
440  INTEGER :: ilev, ibc, iec
441  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend, icoff, ijcoff
442 
443  REAL(RFREAL), POINTER :: cv(:,:), cvn(:,:), cvn1(:,:), cvn2(:,:)
444 
445  TYPE(t_global), POINTER :: global
446 
447 #ifdef TURB
448  LOGICAL :: turbused
449 #endif
450 
451 !******************************************************************************
452 
453  global => region%global
454 
455  CALL registerfunction( global,'RFLO_DualTstShift',&
456  'RFLO_DualTstUtil.F90' )
457 
458  ilev = region%currLevel
459  CALL rflo_getdimensdummy( region,ilev,idcbeg,idcend, &
460  jdcbeg,jdcend,kdcbeg,kdcend )
461  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
462  ibc = indijk(idcbeg,jdcbeg,kdcbeg,icoff,ijcoff)
463  iec = indijk(idcend,jdcend,kdcend,icoff,ijcoff)
464 
465  cv => region%levels(ilev)%mixt%cv
466  cvn => region%levels(ilev)%mixt%cvn
467  cvn1 => region%levels(ilev)%mixt%cvn1
468  cvn2 => region%levels(ilev)%mixt%cvn2
469 
470  DO ic=ibc,iec
471  cvn2(cv_mixt_dens,ic) = cvn1(cv_mixt_dens,ic)
472  cvn2(cv_mixt_xmom,ic) = cvn1(cv_mixt_xmom,ic)
473  cvn2(cv_mixt_ymom,ic) = cvn1(cv_mixt_ymom,ic)
474  cvn2(cv_mixt_zmom,ic) = cvn1(cv_mixt_zmom,ic)
475  cvn2(cv_mixt_ener,ic) = cvn1(cv_mixt_ener,ic)
476  cvn1(cv_mixt_dens,ic) = cvn(cv_mixt_dens,ic)
477  cvn1(cv_mixt_xmom,ic) = cvn(cv_mixt_xmom,ic)
478  cvn1(cv_mixt_ymom,ic) = cvn(cv_mixt_ymom,ic)
479  cvn1(cv_mixt_zmom,ic) = cvn(cv_mixt_zmom,ic)
480  cvn1(cv_mixt_ener,ic) = cvn(cv_mixt_ener,ic)
481  cvn(cv_mixt_dens,ic) = cv(cv_mixt_dens,ic)
482  cvn(cv_mixt_xmom,ic) = cv(cv_mixt_xmom,ic)
483  cvn(cv_mixt_ymom,ic) = cv(cv_mixt_ymom,ic)
484  cvn(cv_mixt_zmom,ic) = cv(cv_mixt_zmom,ic)
485  cvn(cv_mixt_ener,ic) = cv(cv_mixt_ener,ic)
486  ENDDO
487 
488 ! turbulence part ------------------------------------------------------------
489 
490 #ifdef TURB
491  turbused = (region%mixtInput%flowModel == flow_navst .AND. &
492  region%mixtInput%turbModel /= turb_model_none)
493 
494  IF (turbused) THEN
495  IF (region%turbInput%modelClass == model_rans .AND. &
496  region%turbInput%nCv > 0) THEN
497 
498  cv => region%levels(ilev)%turb%cv
499  cvn => region%levels(ilev)%turb%cvn
500  cvn1 => region%levels(ilev)%turb%cvn1
501  cvn2 => region%levels(ilev)%turb%cvn2
502 
503  DO ic=ibc,iec
504  DO id=1,region%turbInput%nCv
505  cvn2(id,ic) = cvn1(id,ic)
506  cvn1(id,ic) = cvn(id,ic)
507  cvn(id,ic) = cv(id,ic)
508  ENDDO
509  ENDDO
510  ENDIF ! rans
511  ENDIF ! turbused
512 #endif
513 
514  CALL deregisterfunction( global )
515 
516 END SUBROUTINE rflo_dualtstshift
517 
518 !******************************************************************************
519 !
520 ! RCS Revision history:
521 !
522 ! $Log: RFLO_DualTstUtil.F90,v $
523 ! Revision 1.6 2008/12/06 08:44:26 mtcampbe
524 ! Updated license.
525 !
526 ! Revision 1.5 2008/11/19 22:17:37 mtcampbe
527 ! Added Illinois Open Source License/Copyright
528 !
529 ! Revision 1.4 2005/10/31 21:09:36 haselbac
530 ! Changed specModel and SPEC_MODEL_NONE
531 !
532 ! Revision 1.3 2004/12/09 22:16:34 wasistho
533 ! added data turbulence
534 !
535 ! Revision 1.2 2004/12/04 07:22:58 wasistho
536 ! finish up dual tst
537 !
538 ! Revision 1.1 2004/11/29 20:51:39 wasistho
539 ! lower to upper case
540 !
541 ! Revision 1.6 2003/11/20 16:40:39 mdbrandy
542 ! Backing out RocfluidMP changes from 11-17-03
543 !
544 ! Revision 1.2 2003/07/08 21:21:37 jblazek
545 ! Modified start up procedure for dual-time stepping.
546 !
547 ! Revision 1.1 2003/07/03 21:48:45 jblazek
548 ! Implemented dual-time stepping.
549 !
550 !******************************************************************************
551 
552 
553 
554 
555 
556 
557 
558 
559 
560 
subroutine rflo_dualtststerm(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
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
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
**********************************************************************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_dualtstpredict(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 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 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
**********************************************************************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
subroutine rflo_dualtstshift(region)
blockLoc i
Definition: read.cpp:79
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE idcbeg
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 jdcend
j indices j
Definition: Indexing.h:6
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE jpcend
unsigned long id(const Leda_like_handle &x)
Definition: Handle.h:107
**********************************************************************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 mixtureproperties(region, inBeg, inEnd, gasUpdate)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_getdimensphys(region, iLev, ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend)