Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TURB_RansSAVisFlux.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: compute SA viscous flux: nutot*d_j(tilde[nu])
26 !
27 ! Description: this routine compute d_j(tilde[nu]), while nutot is given
28 ! nutot = nu_l+nu_t with l=laminar, t=turbulent
29 !
30 ! Input: region = data of current region
31 !
32 ! Output: region%levels%turb%diss = viscous flux added to SA dissipation.
33 !
34 ! Notes: none.
35 !
36 !******************************************************************************
37 !
38 ! $Id: TURB_RansSAVisFlux.F90,v 1.12 2008/12/06 08:44:42 mtcampbe Exp $
39 !
40 ! Copyright: (c) 2003 by the University of Illinois
41 !
42 !******************************************************************************
43 
44 SUBROUTINE turb_ranssavisflux( region )
45 
46  USE moddatatypes
47  USE modbndpatch, ONLY: t_patch
48  USE moddatastruct, ONLY : t_region
49 #ifdef RFLO
52 
53 #include "Indexing.h"
54 #endif
55 #ifdef RFLU
59 #endif
61  USE moderror
62  USE modparameters
64  IMPLICIT NONE
65 
66 ! ... parameters
67 #ifdef RFLO
68  TYPE(t_region) :: region
69 #endif
70 #ifdef RFLU
71  TYPE(t_region), POINTER :: region
72 #endif
73 
74 ! ... loop variables
75  INTEGER :: i, j, k, ic, ipatch
76 
77 ! ... local variables
78  INTEGER :: ibegv, iendv, ibegg, iendg, ijkn, ijkc0, ijkc1
79  REAL(RFREAL) :: cb2, opcb2, rsigma, beta, rhoa, mua, rnua
80  REAL(RFREAL) :: nuf, nuc, nutilx, nutily, nutilz, fd
81  REAL(RFREAL) :: sface(3)
82  REAL(RFREAL), POINTER :: cv(:,:), tv(:,:), tcv(:,:), tdiss(:,:)
83  REAL(RFREAL), POINTER :: vol(:)
84 
85 #ifdef RFLO
86  INTEGER :: ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend
87  INTEGER :: ilev, icoff, ijcoff, inoff, ijnoff
88  REAL(RFREAL), POINTER :: avgco(:,:), sf(:,:), grad(:,:)
89 #endif
90 #ifdef RFLU
91  INTEGER, POINTER :: f2c(:,:)
92  REAL(RFREAL), POINTER :: fn(:,:), grad(:,:,:)
93  TYPE(t_patch), POINTER :: ppatch
94 #endif
95 
96 !******************************************************************************
97 
98  CALL registerfunction( region%global,'TURB_RansSAVisFlux',&
99  'TURB_RansSAVisFlux.F90' )
100 
101 ! get dimensions and pointers ------------------------------------------------
102 
103 #ifdef RFLO
104  ilev = region%currLevel
105  cv => region%levels(ilev)%mixt%cv
106  tv => region%levels(ilev)%mixt%tv
107  tcv => region%levels(ilev)%turb%cv
108  tdiss => region%levels(ilev)%turb%diss
109  vol => region%levels(ilev)%grid%vol
110 
111  CALL rflo_getdimensphys( region,ilev,ipcbeg,ipcend, &
112  jpcbeg,jpcend,kpcbeg,kpcend )
113  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
114  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
115  ibegv = cv_sa_nutil
116  iendv = cv_sa_nutil
117  ibegg = gr_sa_nutilx
118  iendg = gr_sa_nutilz
119 #endif
120 #ifdef RFLU
121  cv => region%mixt%cv
122  tv => region%mixt%tv
123  tcv => region%turb%cv
124  tdiss => region%turb%diss
125  vol => region%grid%vol
126  ibegv = cv_sa_nutil
127  iendv = cv_sa_nutil
128  ibegg = gr_sa_nutilx
129  iendg = gr_sa_nutilx
130 #endif
131 
132 ! get needed quantities
133 
134  cb2 = region%turbInput%const(mc_sa_cb2)
135  rsigma = region%turbInput%const(mc_sa_rsig)
136  beta = region%mixtInput%betrk(region%irkStep)*rsigma
137  opcb2 = 1._rfreal+cb2
138 
139 ! get gradients of tilde[nu]
140 
141 #ifdef RFLO
142  CALL rflo_calcgradvector( region,ibegv,iendv,ibegg,iendg, &
143  region%levels(ilev)%turb%cv, &
144  region%levels(ilev)%turb%gradi, &
145  region%levels(ilev)%turb%gradj, &
146  region%levels(ilev)%turb%gradk )
147 #endif
148 #ifdef RFLU
149  CALL rflu_computegradfaceswrapper( region,ibegv,iendv,ibegg,iendg, &
150  region%turb%cv,region%turb%gradi )
151  DO ipatch = 1,region%grid%nPatches
152  ppatch => region%patches(ipatch)
153 
154  IF ( rflu_decideneedbgradface(region,ppatch) .EQV. .true. ) THEN
155  CALL rflu_computegradbfaceswrapper( region,ppatch,ibegv,iendv,ibegg,iendg, &
156  region%turb%cv,region%turb%bGradi )
157  END IF ! RFLU_DecideNeedBGradFace
158  END DO ! iPatch
159 #endif
160 
161 ! interior fluxes -------------------------------------------------------------
162 
163  CALL computeflux( diri )
164 #ifdef RFLO
165  CALL computeflux( dirj )
166  CALL computeflux( dirk )
167 #endif
168 
169 ! fluxes through boundaries ---------------------------------------------------
170 #ifdef RFLO
171  DO ipatch=1,region%nPatches
172  CALL turb_ranssavisfluxpatch( region,region%levels(ilev)%patches(ipatch) )
173  ENDDO
174 #endif
175 #ifdef RFLU
176  DO ipatch = 1,region%grid%nPatches
177  CALL turb_ranssavisfluxpatch( region,region%patches(ipatch) )
178  END DO ! ipatch
179 #endif
180 
181 ! finalize --------------------------------------------------------------------
182 
183  CALL deregisterfunction( region%global )
184 
185 ! =============================================================================
186 ! Flux computation subroutines
187 ! =============================================================================
188 
189 CONTAINS
190 
191  SUBROUTINE computeflux( ijk )
192 
193 ! ... parameters
194  INTEGER :: ijk
195 
196 ! ... local variables
197  INTEGER :: ibeg,iend,jbeg,jend,kbeg,kend, iadd,jadd,kadd
198  REAL(RFREAL) :: ac0, ac1
199 
200 ! - Set limits and pointers ---------------------------------------------------
201 
202 #ifdef RFLO
203  IF (ijk==diri) THEN
204  ibeg = ipcbeg+1
205  iend = ipcend
206  jbeg = jpcbeg
207  jend = jpcend
208  kbeg = kpcbeg
209  kend = kpcend
210  iadd = -1
211  jadd = 0
212  kadd = 0
213  grad => region%levels(ilev)%turb%gradi
214  sf => region%levels(ilev)%grid%si
215  avgco => region%levels(ilev)%grid%c2fCoI
216  ELSEIF (ijk==dirj) THEN
217  ibeg = ipcbeg
218  iend = ipcend
219  jbeg = jpcbeg+1
220  jend = jpcend
221  kbeg = kpcbeg
222  kend = kpcend
223  iadd = 0
224  jadd = -1
225  kadd = 0
226  grad => region%levels(ilev)%turb%gradj
227  sf => region%levels(ilev)%grid%sj
228  avgco => region%levels(ilev)%grid%c2fCoJ
229  ELSEIF (ijk==dirk) THEN
230  ibeg = ipcbeg
231  iend = ipcend
232  jbeg = jpcbeg
233  jend = jpcend
234  kbeg = kpcbeg+1
235  kend = kpcend
236  iadd = 0
237  jadd = 0
238  kadd = -1
239  grad => region%levels(ilev)%turb%gradk
240  sf => region%levels(ilev)%grid%sk
241  avgco => region%levels(ilev)%grid%c2fCoK
242  ENDIF
243 #endif
244 #ifdef RFLU
245  ibeg = 1
246  iend = region%grid%nFaces
247  f2c => region%grid%f2c
248  grad => region%turb%gradi
249  fn => region%grid%fn
250 #endif
251 
252 ! -- flux in ijk-direction (except through boundary) --------------------------
253 
254 #ifdef RFLO
255  DO k=kbeg,kend
256  DO j=jbeg,jend
257  DO i=ibeg,iend
258 
259  ijkc0 = indijk(i ,j ,k ,icoff,ijcoff)
260  ijkc1 = indijk(i+iadd,j+jadd,k+kadd,icoff,ijcoff)
261  ijkn = indijk(i ,j ,k ,inoff,ijnoff)
262  ac0 = avgco(2,ijkn)
263  ac1 = avgco(1,ijkn)
264  sface(1)= sf(xcoord,ijkn)
265  sface(2)= sf(ycoord,ijkn)
266  sface(3)= sf(zcoord,ijkn)
267 #endif
268 #ifdef RFLU
269  ac0 = 0.5_rfreal
270  ac1 = 0.5_rfreal
271  DO ijkn = ibeg,iend
272  ijkc0 = f2c(1,ijkn)
273  ijkc1 = f2c(2,ijkn)
274  sface(1)= fn(xcoord,ijkn)*fn(xyzmag,ijkn)
275  sface(2)= fn(ycoord,ijkn)*fn(xyzmag,ijkn)
276  sface(3)= fn(zcoord,ijkn)*fn(xyzmag,ijkn)
277 #endif
278  rhoa = ac0*cv(cv_mixt_dens ,ijkc0)+ac1*cv(cv_mixt_dens ,ijkc1)
279  mua = ac0*tv(tv_mixt_muel ,ijkc0)+ac1*tv(tv_mixt_muel ,ijkc1)
280  rnua = ac0*tcv(cv_sa_nutil ,ijkc0)+ac1*tcv(cv_sa_nutil ,ijkc1)
281  nuf = (rnua + mua)/rhoa
282  nuc = (tcv(cv_sa_nutil ,ijkc0) + tv(tv_mixt_muel ,ijkc0))/ &
283  cv(cv_mixt_dens ,ijkc0)
284 
285 #ifdef RFLO
286  nutilx = grad(gr_sa_nutilx,ijkn)
287  nutily = grad(gr_sa_nutily,ijkn)
288  nutilz = grad(gr_sa_nutilz,ijkn)
289 #endif
290 #ifdef RFLU
291  nutilx = grad(xcoord,gr_sa_nutilx,ijkn)
292  nutily = grad(ycoord,gr_sa_nutilx,ijkn)
293  nutilz = grad(zcoord,gr_sa_nutilx,ijkn)
294 #endif
295 
296  fd = beta*(nuf*opcb2-nuc*cb2)* &
297  (nutilx*sface(1)+nutily*sface(2)+nutilz*sface(3))
298 
299  tdiss(cv_sa_nutil,ijkc0) = tdiss(cv_sa_nutil,ijkc0) + fd
300  tdiss(cv_sa_nutil,ijkc1) = tdiss(cv_sa_nutil,ijkc1) - fd
301 
302 #ifdef RFLO
303  ENDDO ! i
304  ENDDO ! j
305  ENDDO ! k
306 #else
307  ENDDO ! ijkN
308 #endif
309 
310  END SUBROUTINE computeflux
311 
312 END SUBROUTINE turb_ranssavisflux
313 
314 !******************************************************************************
315 !
316 ! RCS Revision history:
317 !
318 ! $Log: TURB_RansSAVisFlux.F90,v $
319 ! Revision 1.12 2008/12/06 08:44:42 mtcampbe
320 ! Updated license.
321 !
322 ! Revision 1.11 2008/11/19 22:17:54 mtcampbe
323 ! Added Illinois Open Source License/Copyright
324 !
325 ! Revision 1.10 2006/08/19 15:40:38 mparmar
326 ! Added use of RFLU_DecideNeedBGradFace
327 !
328 ! Revision 1.9 2006/04/07 15:06:06 haselbac
329 ! Bug fix: Incorrect ifs
330 !
331 ! Revision 1.8 2006/04/07 14:56:02 haselbac
332 ! Adapted to changes in f and bf grad routines
333 !
334 ! Revision 1.7 2005/12/20 20:43:51 wasistho
335 ! adapted to changing in Rocflu on face gradient routines
336 !
337 ! Revision 1.6 2004/08/02 23:08:31 wasistho
338 ! shift location of lines defining ac0 and ac1
339 !
340 ! Revision 1.5 2004/08/02 21:55:39 wasistho
341 ! replaced cell2face midpoint by linear averaging
342 !
343 ! Revision 1.4 2004/03/27 02:16:42 wasistho
344 ! compiled with Rocflu
345 !
346 ! Revision 1.3 2004/03/24 03:37:02 wasistho
347 ! prepared for RFLU
348 !
349 ! Revision 1.2 2004/03/20 03:28:29 wasistho
350 ! prepared for RFLU
351 !
352 ! Revision 1.1 2004/03/05 04:37:00 wasistho
353 ! changed nomenclature
354 !
355 ! Revision 1.5 2003/10/25 22:07:26 wasistho
356 ! modified non-conservative diffusion term
357 !
358 ! Revision 1.4 2003/10/21 01:34:19 wasistho
359 ! loop in computation of gradCell
360 !
361 ! Revision 1.3 2003/10/20 20:28:21 wasistho
362 ! made consistent with compressible SA formulation
363 !
364 ! Revision 1.2 2003/10/10 20:35:06 wasistho
365 ! multiplied SA viscous fluxes by 1/sigma through beta
366 !
367 ! Revision 1.1 2003/10/07 02:17:03 wasistho
368 ! initial installation of RaNS-SA and DES
369 !
370 !
371 !******************************************************************************
372 
373 
374 
375 
376 
377 
378 
subroutine, public rflu_computegradfaceswrapper(pRegion, iBegVar, iEndVar, iBegGrad, iEndGrad, var, grad)
**********************************************************************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 ibeg
subroutine turb_ranssavisfluxpatch(region, patch)
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
LOGICAL function rflu_decideneedbgradface(pRegion, pPatch)
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
**********************************************************************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, public rflu_computegradbfaceswrapper(pRegion, pPatch, iBegVar, iEndVar, iBegGrad, iEndGrad, var, grad)
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 knode iend
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE ipcbeg
blockLoc i
Definition: read.cpp:79
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
subroutine turb_ranssavisflux(region)
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
**********************************************************************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 knode jend
**********************************************************************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 knode jbeg
subroutine computeflux(ijk)
**********************************************************************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 knode kbeg
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine rflo_getdimensphys(region, iLev, ipcbeg, ipcend, jpcbeg, jpcend, kpcbeg, kpcend)
subroutine rflo_calcgradvector(region, iBegV, iEndV, iBegG, iEndG, var, gradi, gradj, gradk)