Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TURB_InitSolution.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: Initialisation of TURB solution
26 !
27 ! Description: Besides initialisation of TURB variables, in case non-uniform
28 ! filter is selected, non-uniform filter coefficients and
29 ! averaging coefficients are computed by calling the corresponding
30 ! routines. If wlm is active, define wlm mapping coefficients and
31 ! copy or interpolate wlm patch vals from level 1 to other levels.
32 !
33 ! Input: region = data of current region
34 !
35 ! Output: mueT, tCoT and cDyn get initial values. Wlm mapping coefficients
36 ! initiated and wlm patch vals interpolated to other levels.
37 !
38 ! Notes: cDyn is set to zero every stage in ViscousFluxes.
39 ! Non-uniform quantities are recomputed in ViscousFluxes everytime
40 ! the grid moves.
41 !
42 !******************************************************************************
43 !
44 ! $Id: TURB_InitSolution.F90,v 1.20 2009/08/26 12:28:52 mtcampbe Exp $
45 !
46 ! Copyright: (c) 2001 by the University of Illinois
47 !
48 !******************************************************************************
49 
50 SUBROUTINE turb_initsolution( region ) ! PUBLIC
51 
52  USE moddatatypes
53  USE modbndpatch, ONLY : t_patch
54  USE moddatastruct, ONLY : t_region
55  USE modgrid, ONLY : t_grid
56  USE modturbulence, ONLY : t_turb
57  USE modglobal, ONLY : t_global
59 #ifdef RFLO
64 #include "Indexing.h"
65 #endif
66 #ifdef RFLU
69 #endif
70  USE moderror
71  USE modparameters
73  IMPLICIT NONE
74 
75 ! ... parameters
76 #ifdef RFLO
77  TYPE(t_region) :: region
78 #endif
79 #ifdef RFLU
80  TYPE(t_region), TARGET :: region
81 #endif
82 
83 ! ... loop variables
84  INTEGER :: ipatch, in, l, ifl
85 
86 ! ... local variables
87  CHARACTER(CHRLEN) :: rcsidentstring
88  TYPE(t_global), POINTER :: global
89  TYPE(t_grid) , POINTER :: grid
90  TYPE(t_turb), POINTER :: turb
91  TYPE(t_patch), POINTER :: patch1, patch
92 
93  LOGICAL :: dowlm
94  INTEGER :: turbmodel
95  REAL(RFREAL) :: triploc(xcoord:zcoord), treshold
96  REAL(RFREAL), POINTER :: tv(:,:), tcv(:,:), tcvold(:,:), tdv(:,:), vort(:,:)
97  REAL(RFREAL), POINTER :: dsterm(:,:)
98 #ifdef RFLO
99  INTEGER :: ilev, inoff, ijnoff, ibn, ien
100  INTEGER :: idnbeg, idnend, jdnbeg, jdnend, kdnbeg, kdnend, errorflag
101 #endif
102 
103  CHARACTER(2*CHRLEN+17) :: fname
104  LOGICAL :: fileexists
105 
106 #ifdef RFLU
107  INTEGER :: ibc, iec, ibn, ien, ic, ifg, ifgbeg
108 #endif
109 !******************************************************************************
110 
111  rcsidentstring = '$RCSfile: TURB_InitSolution.F90,v $'
112 
113  global => region%global
114  CALL registerfunction( global,'TURB_InitSolution',&
115  'TURB_InitSolution.F90' )
116 
117 ! pre procedures -----------------------------------------------------------
118 
119 #ifdef RFLU
120  ibc = 1
121  iec = region%grid%nCellsTot
122  CALL mixtureproperties( region,ibc,iec,.true. )
123 #endif
124 
125 ! get dimensions -----------------------------------------------------------
126 
127 #ifdef RFLO
128  ilev = region%currLevel
129  CALL rflo_getdimensdummynodes( region,ilev,idnbeg,idnend, &
130  jdnbeg,jdnend,kdnbeg,kdnend )
131  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
132  ibn = indijk(idnbeg,jdnbeg,kdnbeg,inoff,ijnoff)
133  ien = indijk(idnend,jdnend,kdnend,inoff,ijnoff)
134 #endif
135 #ifdef RFLU
136  ibn = 1
137  ien = region%grid%nFaces
138 #endif
139 
140 ! get parameters and pointers ----------------------------------------------
141 
142  turbmodel = region%mixtInput%turbModel
143 
144 #ifdef RFLO
145  grid => region%levels(ilev)%grid
146  turb => region%levels(ilev)%turb
147  tv => region%levels(ilev)%mixt%tv
148 
149  IF (region%turbInput%nDv > 0) THEN
150  tdv => turb%dv
151  ENDIF
152  IF (region%turbInput%nCv > 0) THEN
153  tcv => turb%cv
154  tcvold => turb%cvOld
155  dsterm => turb%dsterm
156  ENDIF
157 #endif
158 #ifdef RFLU
159  grid => region%grid
160  turb => region%turb
161  tv => region%mixt%tv
162 
163  IF (region%turbInput%nDv > 0) THEN
164  tdv => region%turb%dv
165  ENDIF
166  IF (region%turbInput%nCv > 0) THEN
167  tcv => region%turb%cv
168  tcvold => region%turb%cvOld
169  dsterm => region%turb%dsterm
170  ENDIF
171 #endif
172 
173 ! initialize turbulent viscosity and thermal conductivity at cells (tv of
174 ! NS system), turbulence variables (turb.cvOld, dv, vorticities, etc),
175 ! and metrics pertinent to turbulence
176 
177 ! general ---------------------------------------------------------
178 ! first check if it's a restart from a laminar run
179  IF (global%solutFormat == format_ascii .OR. global%solutFormat == format_hdf) THEN
180  WRITE(fname,'(A,1PE11.5)') trim(global%inDir)//trim(global%casename)//'.turba_', &
181  global%timeStamp
182  INQUIRE(file=fname,exist=fileexists)
183  ELSE IF (global%solutFormat == format_binary) THEN
184  WRITE(fname,'(A,I6.6)') trim(global%inDir)//trim(global%casename)//'.turbb_', &
185  global%currentIter
186  INQUIRE(file=fname,exist=fileexists)
187  ELSE
188  CALL errorstop( global,err_unknown_format,__line__ )
189  ENDIF
190 
191  IF ((global%flowType == flow_unsteady .AND. &
192  global%timeStamp <= 0._rfreal) .OR. &
193  (global%flowType == flow_steady .AND. &
194  global%currentIter <= 0) .OR. &
195  (global%flowType == flow_unsteady .AND. &
196  global%timeStamp > 0._rfreal .AND. &
197  fileexists .EQV. .false.) .OR. &
198  (global%flowType == flow_steady .AND. &
199  global%currentIter > 0 .AND. &
200  fileexists .EQV. .false.)) THEN
201  tv(tv_mixt_muet,:) = 0._rfreal
202  global%esg1Sum = 0._rfreal ! pertinent to
203  global%esg4Sum = 0._rfreal ! LES energy model
204  IF (region%turbInput%nCv > 0) THEN
205 #ifdef RFLO
206  tcv(cv_sa_nutil,:)= tv(tv_mixt_muel,:) ! pertinent to RaNS
207 #endif
208 #ifdef RFLU
209  tcv(cv_sa_nutil,:)= region%mixtInput%refVisc ! mixtProp, dv unknown yet
210 #endif
211  tcvold(:,:) = 0._rfreal
212  ENDIF
213  ENDIF
214  tv(tv_mixt_tcot,:) = 0._rfreal
215 
216  IF (region%turbInput%nCv > 0) THEN
217  dsterm(:,:) = 0._rfreal
218  ENDIF
219 
220  IF (region%turbInput%nDv > 0) THEN
221  tdv(:,:) = 0._rfreal
222  ENDIF
223 
224  IF (ASSOCIATED( turb%vort )) THEN
225  turb%vort = 0._rfreal
226  ENDIF
227 
228 ! model dependent ---------------------------------------
229 
230  IF ((region%mixtInput%turbModel == turb_model_sa) .OR. &
231  (region%mixtInput%turbModel == turb_model_dessa) .OR. &
232  (region%mixtInput%turbModel == turb_model_hdessa)) THEN
233  CALL turb_ranssageteddyvis( region ) ! nutilde to muet
234  ENDIF
235 
236 ! metrics related ----------------------------------------
237 
238 ! compute face volumes needed for lesMij
239  IF ((turbmodel==turb_model_fixsmag) .OR. &
240  (turbmodel==turb_model_dynsmag) .OR. &
241  (turbmodel==turb_model_dynmixd)) THEN
242 #ifdef RFLO
243  CALL turb_flofacevolume( region,diri )
244  CALL turb_flofacevolume( region,dirj )
245  CALL turb_flofacevolume( region,dirk )
246 #endif
247 #ifdef RFLU
248  CALL turb_flufacevolume( region )
249 #endif
250  ENDIF
251 
252 #ifdef RFLO
253 ! compute filter coefficients
254 
255  IF (((turbmodel==turb_model_scalsim) .OR. &
256  (turbmodel==turb_model_dynsmag) .OR. &
257  (turbmodel==turb_model_dynmixd)) .AND. &
258  (region%turbInput%filterType == filtype_nonunif)) THEN
259 
260  ALLOCATE( turb%workI(2,ibn:ien),stat=errorflag )
261  ALLOCATE( turb%workJ(2,ibn:ien),stat=errorflag )
262  ALLOCATE( turb%workK(2,ibn:ien),stat=errorflag )
263  global%error = errorflag
264  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
265 
266  CALL turb_flofacewidth( region )
267  CALL turb_flolesgencocc( region )
268  CALL turb_flolesgencoff( region )
269  DEALLOCATE( turb%workI,turb%workJ,turb%workK )
270  ENDIF
271 #endif
272 
273 ! initialize zero-one fields
274 
275  IF (region%turbInput%nZof > 0) THEN
276 #ifdef RFLO
277  turb%zofi = 1._rfreal
278  turb%zofj = 1._rfreal
279  turb%zofk = 1._rfreal
280 #endif
281 #ifdef RFLU
282  turb%zofi = 1._rfreal
283  turb%bZofi = 1._rfreal
284 #endif
285  ENDIF
286 
287 ! create zero-one fields
288 
289  IF (turbmodel==turb_model_fixsmag .OR. &
290  turbmodel==turb_model_dynsmag .OR. &
291  turbmodel==turb_model_dynmixd) THEN
292  triploc(:) = region%turbInput%xyzSmag(:)
293  treshold = -huge( 1.0_rfreal )/1000._rfreal
294 
295  IF ((triploc(xcoord) > treshold) .OR. &
296  (triploc(ycoord) > treshold) .OR. &
297  (triploc(zcoord) > treshold)) THEN
298 
299 #ifdef RFLO
300  DO in = ibn,ien
301  DO l = xcoord,zcoord
302  IF (grid%cfcI(l,in) < triploc(l)) THEN
303  turb%zofi(l,zof_les_eddyvis,in) = 0._rfreal
304  ELSE
305  turb%zofi(l,zof_les_eddyvis,in) = 1._rfreal
306  ENDIF
307  ENDDO ! l
308  DO l = xcoord,zcoord
309  IF (grid%cfcJ(l,in) < triploc(l)) THEN
310  turb%zofj(l,zof_les_eddyvis,in) = 0._rfreal
311  ELSE
312  turb%zofj(l,zof_les_eddyvis,in) = 1._rfreal
313  ENDIF
314  ENDDO ! l
315  DO l = xcoord,zcoord
316  IF (grid%cfcK(l,in) < triploc(l)) THEN
317  turb%zofk(l,zof_les_eddyvis,in) = 0._rfreal
318  ELSE
319  turb%zofk(l,zof_les_eddyvis,in) = 1._rfreal
320  ENDIF
321  ENDDO ! l
322  ENDDO ! iN
323 #endif
324 #ifdef RFLU
325  DO in = ibn,ien
326  DO l = xcoord,zcoord
327  IF (grid%fc(l,in) < triploc(l)) THEN
328  turb%zofi(l,zof_les_eddyvis,in) = 0._rfreal
329  ELSE
330  turb%zofi(l,zof_les_eddyvis,in) = 1._rfreal
331  ENDIF
332  ENDDO ! l
333  ENDDO ! iN
334  DO ipatch = 1,grid%nPatches
335  patch => region%patches(ipatch)
336 ! TEMPORARY : removing usage of bf2bg from everywhere
337 ! ifgBeg = patch%bf2bg(BF2BG_BEG)
338 
339  DO ifl = 1,patch%nBFaces
340  ic = patch%bf2c(ifl)
341  ifg = ifl + ifgbeg-1
342 
343  DO l = xcoord,zcoord
344  IF (grid%cofg(l,ic) < triploc(l)) THEN
345  turb%bZofi(l,zof_les_eddyvis,ifg) = 0._rfreal
346  ELSE
347  turb%bZofi(l,zof_les_eddyvis,ifg) = 1._rfreal
348  ENDIF
349  ENDDO ! l
350  ENDDO ! ifl
351  ENDDO ! iPatch
352 #endif
353 
354  ENDIF ! triploc
355  ENDIF ! turbModel
356 
357 ! if applicable, initiate metric variables and utau of wlm
358 
359 #ifdef RFLO
360  DO ipatch=1,region%nPatches
361  patch1 => region%levels(1)%patches(ipatch)
362  patch => region%levels(ilev)%patches(ipatch)
363 #endif
364 #ifdef RFLU
365  DO ipatch=1,region%grid%nPatches
366  patch => region%patches(ipatch)
367 #endif
368 
369  dowlm = .false.
370 #ifdef RFLO
371  IF (patch%bcType>=bc_noslipwall .AND. &
372  patch%bcType<=bc_noslipwall+bc_range) THEN ! my boundary type
373  IF (patch%valBola%switches(wlm_input_model) /= wlm_model_nomodel) THEN
374  dowlm = .true.
375  ENDIF
376  ENDIF
377 #endif
378 
379  IF (dowlm .eqv. .true.) THEN
380 
381 ! --- get initial estimate of friction velocity utau
382  CALL turb_wlminitia( region,patch )
383 
384 #ifdef RFLO
385 ! --- compute mapping coefficients from body fitted to cartesian and other metrics
386  CALL turb_flowlmmetric( region,patch )
387 
388  IF (patch%valBola%distrib==bcdat_distrib) THEN
389 ! ----- roughness distribution
390 ! CALL TURB_interpolate2Levels( )
391  CALL errorstop( global,err_val_bcval,__line__,'No variable roughness yet' )
392  ELSE
393 ! ----- distribution has constant value, so copied from a point on patch level 1
394  patch%valBola%vals(:,wlm_vals_rough)= patch1%valBola%vals(1,wlm_vals_rough)
395  ENDIF ! distribution
396 
397  IF (patch%valBola%switches(wlm_input_model) == wlm_model_extern) THEN
398 ! ----- wall stress distribution
399 ! CALL TURB_interpolate2Levels( )
400  ENDIF
401 #endif
402 
403  ENDIF ! doWlm
404  ENDDO ! iPatch
405 
406 ! finalize --------------------------------------------------------
407 
408  CALL deregisterfunction( global )
409 
410 END SUBROUTINE turb_initsolution
411 
412 !******************************************************************************
413 !
414 ! RCS Revision history:
415 !
416 ! $Log: TURB_InitSolution.F90,v $
417 ! Revision 1.20 2009/08/26 12:28:52 mtcampbe
418 ! Ported to Hera. Fixed logical expression syntax errors. Replaced all
419 ! IF (logical_variable) with IF (logical_variable .eqv. .true.) as
420 ! consistent with the specification. Also changed: IF( ASSOCIATED(expr) )
421 ! to IF ( ASSOCIATED(expr) .eqv. .true. ). Intel compilers produce code
422 ! which silently fails for some mal-formed expressions, so these changes
423 ! are a net which should ensure that they are evaluated as intended.
424 !
425 ! Revision 1.19 2009/08/12 04:15:59 mtcampbe
426 ! Major update, bugfix from Abe development, more propagation compatibility,
427 ! some Rocstar IO changes, Ju's temporary clipping fix for turbulence. A bug
428 ! fix for initialization IO.
429 !
430 ! Revision 1.18 2009/06/29 17:15:32 juzhang
431 ! initialization of RANS/DES added for restart from a laminar run
432 !
433 ! Revision 1.17 2008/12/06 08:44:41 mtcampbe
434 ! Updated license.
435 !
436 ! Revision 1.16 2008/11/19 22:17:53 mtcampbe
437 ! Added Illinois Open Source License/Copyright
438 !
439 ! Revision 1.15 2006/08/19 15:40:58 mparmar
440 ! Removed bf2bg
441 !
442 ! Revision 1.14 2006/01/30 23:06:15 wasistho
443 ! removed comment after ifdef RFLU
444 !
445 ! Revision 1.13 2006/01/17 17:51:40 wasistho
446 ! applied tripping to all eddy viscosity models
447 !
448 ! Revision 1.12 2006/01/12 23:46:55 wasistho
449 ! POINTER to TARGET in rflu
450 !
451 ! Revision 1.11 2006/01/12 09:48:49 wasistho
452 ! enabled tripping fixed Smagorinsky
453 !
454 ! Revision 1.10 2005/12/30 23:20:32 wasistho
455 ! exclude rocflu from WLM treatment
456 !
457 ! Revision 1.9 2005/12/29 19:48:01 wasistho
458 ! modified rflu part
459 !
460 ! Revision 1.8 2005/03/09 06:35:01 wasistho
461 ! incorporated HDESSA
462 !
463 ! Revision 1.7 2004/08/04 02:45:47 wasistho
464 ! removed turb%avgCoI,J,K as it is defined as grid%c2fCoI,J,K
465 !
466 ! Revision 1.6 2004/06/19 03:29:48 wasistho
467 ! removed argument iReg in TURB_InitSolution
468 !
469 ! Revision 1.5 2004/06/03 02:10:47 wasistho
470 ! enabled non-uniform fix-Smagorinsky
471 !
472 ! Revision 1.4 2004/03/20 03:28:29 wasistho
473 ! prepared for RFLU
474 !
475 ! Revision 1.3 2004/03/19 02:47:13 wasistho
476 ! prepared for RFLU
477 !
478 ! Revision 1.2 2004/03/12 02:55:35 wasistho
479 ! changed rocturb routine names
480 !
481 ! Revision 1.1 2004/03/05 04:37:00 wasistho
482 ! changed nomenclature
483 !
484 ! Revision 1.12 2004/02/26 21:26:29 wasistho
485 ! initialize esg1Sum, esg4Sum
486 !
487 ! Revision 1.11 2003/10/24 03:46:43 wasistho
488 ! initiate mu_t to mu_l if RaNS is active
489 !
490 ! Revision 1.10 2003/10/21 20:31:50 wasistho
491 ! added dt relaxation in steady flow due to RANS source term
492 !
493 ! Revision 1.9 2003/10/09 22:50:13 wasistho
494 ! mv call to TURB_RansSAGetEddyVis from readSolution to initSolution
495 !
496 ! Revision 1.8 2003/10/07 02:06:03 wasistho
497 ! initial installation of RaNS-SA and DES
498 !
499 ! Revision 1.7 2003/08/08 01:46:24 wasistho
500 ! fixed turb. restart for steady flow
501 !
502 ! Revision 1.6 2003/08/06 15:56:13 wasistho
503 ! added vorticities computation
504 !
505 ! Revision 1.5 2003/08/01 22:17:43 wasistho
506 ! prepared rocturb for Genx
507 !
508 ! Revision 1.4 2003/07/23 15:59:40 wasistho
509 ! prepared more accurate rocturb restart
510 !
511 ! Revision 1.3 2003/05/31 01:46:52 wasistho
512 ! installed turb. wall layer model
513 !
514 ! Revision 1.2 2002/10/16 07:48:19 wasistho
515 ! Enable Fix Smagorinsky
516 !
517 ! Revision 1.1 2002/10/14 23:55:29 wasistho
518 ! Install Rocturb
519 !
520 !
521 !******************************************************************************
522 
523 
524 
525 
526 
527 
528 
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 turb_flofacewidth(region)
subroutine turb_flowlmmetric(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 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
**********************************************************************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
Definition: patch.h:74
subroutine turb_wlminitia(region, patch)
subroutine turb_flolesgencoff(region)
subroutine turb_ranssageteddyvis(region)
subroutine turb_flofacevolume(region, ijk)
subroutine rflo_getdimensdummynodes(region, iLev, idnbeg, idnend, jdnbeg, jdnend, kdnbeg, kdnend)
subroutine turb_initsolution(region)
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_flufacevolume(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 kdnbeg
subroutine turb_flolesgencocc(region)