Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TURB_CheckParamInput.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: Check TURB parameters either specified by user or set in the code.
26 !
27 ! Description: The checking includes the existency and order of parameters.
28 !
29 ! Input: regions = input parameters contained in turbInput of all regions.
30 !
31 ! Output: Error msg.
32 !
33 ! Notes: none.
34 !
35 !******************************************************************************
36 !
37 ! $Id: TURB_CheckParamInput.F90,v 1.19 2009/08/26 12:28:52 mtcampbe Exp $
38 !
39 ! Copyright: (c) 2001 by the University of Illinois
40 !
41 !******************************************************************************
42 
43 SUBROUTINE turb_checkparaminput( regions )
44 
45  USE moddatatypes
46  USE moddatastruct, ONLY : t_region
47  USE modglobal, ONLY : t_global
48  USE modmixture, ONLY : t_mixt_input
49  USE modbndpatch, ONLY : t_patch
50 #ifdef RFLO
52 #endif
53  USE modturbulence
54  USE moderror
55  USE modmpi
56  USE modparameters
58 
59  IMPLICIT NONE
60 
61 ! ... parameters
62  TYPE(t_region), POINTER :: regions(:)
63 
64 ! ... loop variables
65  INTEGER :: ireg, m, ipatch
66 
67 ! ... local variables
68  CHARACTER(CHRLEN) :: rcsidentstring
69  TYPE(t_global), POINTER :: global
70 
71  TYPE(t_mixt_input), POINTER :: mixtinput
72  TYPE(t_turb_input), POINTER :: input
73  TYPE(t_patch), POINTER :: patch1
74  LOGICAL :: turbinactive, fixedgrid, movegrid, wransactive, nonswall
75 
76 #ifdef RFLO
77  INTEGER :: idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend
78  INTEGER :: ilev, maxrange
79 #endif
80 
81 !******************************************************************************
82 
83  rcsidentstring = '$RCSfile: TURB_CheckParamInput.F90,v $'
84 
85  global => regions(1)%global
86  CALL registerfunction( global,'TURB_CheckParamInput',&
87  'TURB_CheckParamInput.F90' )
88 
89  IF ( global%myProcid == masterproc .AND. &
90  global%verbLevel > verbose_none ) THEN
91  WRITE(stdout,'(A,1X,A)') solver_name,'Entering TURB_CheckParamInput...'
92  END IF ! global%verbLevel
93 
94 ! check fixed parameters setting ---------------------------------------------
95 
96 ! fixed parameters for general rocturb
97 
98  IF ((ycoord - xcoord)/=1 .OR. &
99  (zcoord - ycoord)/=1) THEN
100  CALL errorstop( global,err_turb_fixparam,__line__,'XCOORD,YCOORD,ZCOORD' )
101  ENDIF
102 
103 #ifdef RFLO
104  IF (ndir /= 3) THEN
105  CALL errorstop( global,err_turb_fixparam,__line__,'NDIR /= 3' )
106  ENDIF
107  IF ((dirk-dirj /= 1).OR.(dirj-diri /= 1).OR.(diri /= 1)) THEN
108  CALL errorstop( global,err_turb_fixparam,__line__,'DIRI,DIRJ,DIRK' )
109  ENDIF
110 #endif
111 
112  IF ((cv_turb_vvel - cv_turb_uvel /= 1) .OR. &
113  (cv_turb_wvel - cv_turb_vvel /= 1)) THEN
114  CALL errorstop( global,err_turb_fixparam,__line__,'CV_TURB_...' )
115  ENDIF
116 
117  IF ((cv_turb_xmom - cv_turb_dens /= 1) .OR. &
118  (cv_turb_ymom - cv_turb_xmom /= 1) .OR. &
119  (cv_turb_zmom - cv_turb_ymom /= 1)) THEN
120  CALL errorstop( global,err_turb_fixparam,__line__,'CV_TURB_...' )
121  ENDIF
122 
123  IF (((gr_turb_vx - gr_turb_ux)/=1).OR.((gr_turb_wx - gr_turb_vx)/=1).OR. &
124  ((gr_turb_uy - gr_turb_wx)/=1).OR.((gr_turb_vy - gr_turb_uy)/=1).OR. &
125  ((gr_turb_wy - gr_turb_vy)/=1).OR.((gr_turb_uz - gr_turb_wy)/=1).OR. &
126  ((gr_turb_vz - gr_turb_uz)/=1).OR.((gr_turb_wz - gr_turb_vz)/=1)) THEN
127  CALL errorstop( global,err_turb_fixparam,__line__,'GR_TURB_...' )
128  ENDIF
129 
130 #ifdef RFLU
131  IF ((cv_turb_dens /= cv_mixt_dens) .OR. & ! relevant to LesLij, LesMij, LesHij,
132  (cv_turb_xmom /= cv_mixt_xmom) .OR. & ! etc
133  (cv_turb_ymom /= cv_mixt_ymom) .OR. &
134  (cv_turb_zmom /= cv_mixt_zmom)) THEN
135  CALL errorstop( global,err_turb_fixparam,__line__,'CV_TURB_.../= CV_MIXT_...' )
136  ENDIF
137 
138 ! IF ((CV_TURB_DENS /= 1) .OR. & ! relevant to RFLU_InterpCells2Faces, etc
139 ! (E11 /= 1)) THEN
140 ! CALL ErrorStop( global,ERR_TURB_FIXPARAM,__LINE__,'CV_TURB_DES or E11 /= 1' )
141 ! ENDIF
142 #endif
143 
144 ! fixed parameters pertinent to LES
145 
146  IF ((filwidth_one /= 1) .OR. &
147  (filwidth_two /= 2) .OR. &
148  (filwidth_four /= 4)) THEN
149  CALL errorstop( global,err_turb_fixparam,__line__,'FILWIDTH_...' )
150  ENDIF
151 
152 ! fixed parameters pertinent to WLM
153 
154  IF (wlm_vals_xix/=1 .OR. wlm_vals_tauux/=10 .OR. &
155  (wlm_vals_etx-wlm_vals_xix)/=1 .OR. (wlm_vals_ztx-wlm_vals_etx)/=1 .OR. &
156  (wlm_vals_ety-wlm_vals_xiy)/=1 .OR. (wlm_vals_zty-wlm_vals_ety)/=1 .OR. &
157  (wlm_vals_etz-wlm_vals_xiz)/=1 .OR. (wlm_vals_ztz-wlm_vals_etz)/=1 .OR. &
158  (wlm_vals_xiy-wlm_vals_ztx)/=1 .OR. (wlm_vals_xiz-wlm_vals_zty)/=1 .OR. &
159  (wlm_vals_tauuy-wlm_vals_tauux)/=1.OR.(wlm_vals_tauuz-wlm_vals_tauuy)/=1.OR. &
160  (wlm_vals_tauvy-wlm_vals_tauvx)/=1.OR.(wlm_vals_tauvz-wlm_vals_tauvy)/=1.OR. &
161  (wlm_vals_tauwy-wlm_vals_tauwx)/=1.OR.(wlm_vals_tauwz-wlm_vals_tauwy)/=1.OR. &
162  (wlm_vals_tauvx-wlm_vals_tauuz)/=1.OR.(wlm_vals_tauwx-wlm_vals_tauvz)/=1) THEN
163  CALL errorstop( global,err_turb_fixparam,__line__,'WLM_VALS_...' )
164  ENDIF
165 
166 ! check turbulence parameters selection
167 
168  turbinactive = .false.
169  fixedgrid = .false.
170  movegrid = .false.
171  wransactive = .false.
172  nonswall = .true.
173 
174 #ifdef RFLO
175  DO ireg = 1,global%nRegions
176  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
177  regions(ireg)%active==active) THEN ! on my processor
178 #endif
179 #ifdef RFLU
180  DO ireg = lbound(regions,1),ubound(regions,1)
181 #endif
182 
183  mixtinput => regions(ireg)%mixtInput
184  input => regions(ireg)%turbInput
185 
186  IF ((mixtinput%turbModel /= turb_model_none).AND. &
187  (mixtinput%turbModel /= turb_model_fixsmag).AND. &
188  (mixtinput%turbModel /= turb_model_scalsim).AND. &
189  (mixtinput%turbModel /= turb_model_dynsmag).AND. &
190  (mixtinput%turbModel /= turb_model_dynmixd).AND. &
191  (mixtinput%turbModel /= turb_model_sa) .AND. &
192  (mixtinput%turbModel /= turb_model_dessa) .AND. &
193  (mixtinput%turbModel /= turb_model_hdessa)) THEN
194  CALL errorstop( global,err_turb_model,__line__ )
195  ENDIF
196 #ifdef RFLU
197  IF (mixtinput%turbModel==turb_model_dynmixd) THEN
198  CALL errorstop( global,err_turb_model,__line__, &
199  'LES Dynamic Mixed model is not available with unstructured grid' )
200  ENDIF
201 #endif
202  IF ((input%modelClass /= model_rans) .AND. (input%nCv > 0)) THEN
203  CALL errorstop( global,err_turb_fixparam,__line__, &
204  'number of conservative variables > 0 only for RANS/DES' )
205  ENDIF
206 
207  IF ((input%calcVort /= calcvort_no) .AND. &
208  (input%calcVort /= calcvort_fdt) .AND. &
209  (input%calcVort /= calcvort_sdt)) THEN
210  CALL errorstop( global,err_turb_input,__line__,'CALCVORTIC: 0, 1 or 2' )
211  ENDIF
212 
213 #ifdef GENX
214  IF (input%calcVort == calcvort_no) THEN
215  CALL errorstop( global,err_turb_input,__line__, &
216  'Vorticities should always be computed in Genx, CALCVORTIC cannot be 0' )
217  ENDIF
218 #endif
219 
220  IF ((input%nOutField > 1).AND.(input%calcVort == calcvort_no)) THEN
221  CALL errorstop( global,err_turb_input,__line__, &
222  'CALCVORTIC should be > 0 for OUTPUTNUMBER > 1' )
223  ENDIF
224 
225  IF (input%nZof > zof_nelm) THEN
226  CALL errorstop( global,err_turb_fixparam,__line__, &
227  'ZOF_NELM < input%nZof, increase the former' )
228  ENDIF
229 
230 ! --- pertinent to LES
231 
232  IF (input%modelClass == model_les) THEN
233  IF ((mixtinput%turbModel==turb_model_fixsmag).OR. &
234  (mixtinput%turbModel==turb_model_scalsim).OR. &
235  (mixtinput%turbModel==turb_model_dynsmag).OR. &
236  (mixtinput%turbModel==turb_model_dynmixd)) THEN
237  ELSE
238  CALL errorstop( global,err_turb_lesinput,__line__, &
239  'selected turbulence model is not of LES class' )
240  ENDIF
241 
242  IF ((input%nOutField < 1).OR.(input%nOutField > maxoutfld_les)) THEN
243  CALL errorstop( global,err_turb_input,__line__, &
244  'OUTPUTNUMBER for LES out of range' )
245  ENDIF
246 
247  IF ((input%cSmag < 0._rfreal).OR.(input%cSmag > 0.2_rfreal)) THEN
248  CALL errorstop( global,err_turb_lesinput,__line__, &
249  '0<= CSMAGORINSKY <=0.2' )
250  ENDIF
251 
252 #ifdef RFLO
253  IF ((input%filterType /= filtype_uniform) .AND. &
254  (input%filterType /= filtype_nonunif)) THEN
255  CALL errorstop( global,err_turb_lesinput,__line__, &
256  'FILTERTYPE: 0 or 1' )
257  ENDIF
258 
259  IF ((input%deltaType /= deltype_cbrt) .AND. &
260  (input%deltaType /= deltype_sqrt)) THEN
261  CALL errorstop( global,err_turb_lesinput,__line__, &
262  'DELTATYPE: 0 or 1' )
263  ENDIF
264 
265  DO m = diri,dirk
266  IF ((input%filterWidth(m) /= filwidth_zero) .AND. &
267  (input%filterWidth(m) /= filwidth_one) .AND. &
268  (input%filterWidth(m) /= filwidth_two)) THEN
269  CALL errorstop( global,err_turb_lesinput,__line__, &
270  'FILTERWIDTH: 0,1 or 2' )
271  ENDIF
272  IF ((input%homDir(m) /= off) .AND. &
273  (input%homDir(m) /= active)) THEN
274  CALL errorstop( global,err_turb_lesinput,__line__, &
275  'HOMOGENDIR: 0 or 1' )
276  ENDIF
277  ENDDO
278 #endif
279 #ifdef RFLU
280  IF ((input%filterWidth(diri) /= filwidth_zero) .AND. &
281  (input%filterWidth(diri) /= filwidth_one) .AND. &
282  (input%filterWidth(diri) /= filwidth_two)) THEN
283  CALL errorstop( global,err_turb_lesinput,__line__, &
284  'FILTERWIDTH: 0,1 or 2' )
285  ENDIF
286 #endif
287  IF ((input%engModel /= off) .AND. &
288  (input%engModel /= active)) THEN
289  CALL errorstop( global,err_turb_lesinput,__line__, &
290  'ENERGYMODEL: 0 or 1' )
291  ENDIF
292 
293  ENDIF ! modelClass LES
294 
295 ! --- pertinent to RaNS/DES
296 
297  IF (input%modelClass == model_rans) THEN
298  IF ((mixtinput%turbModel==turb_model_sa).OR. &
299  (mixtinput%turbModel==turb_model_dessa).OR. &
300  (mixtinput%turbModel==turb_model_hdessa)) THEN
301  IF (input%wDistMethod /= wdist_direct) THEN
302  CALL errorstop( global,err_turb_ransinput,__line__, &
303  'only direct WALLDISTMETHOD (0) currently valid for SA/DES' )
304  ENDIF
305 ! IF ((mixtInput%moveGrid .eqv. .true.) .AND. (input%wDistMethod==WDIST_DIRECT)) THEN
306 ! CALL ErrorStop( global,ERR_TURB_RANSINPUT,__LINE__, &
307 ! 'direct WALLDISTMETHOD (0) is not efficient for moving grid' )
308 ! ENDIF
309  IF (input%functV1 /= sa_fv1_pow3 .AND. &
310  input%functV1 /= sa_fv1_pow2) THEN
311  CALL errorstop( global,err_turb_ransinput,__line__, &
312  'selected formula for SA function fv1 is invalid' )
313  ENDIF
314  ELSE
315  CALL errorstop( global,err_turb_ransinput,__line__, &
316  'selected turbulence model is not of RANS/DES class' )
317  ENDIF
318 
319  IF ((input%nOutField < 1).OR.(input%nOutField > maxoutfld_rans)) THEN
320  CALL errorstop( global,err_turb_input,__line__, &
321  'OUTPUTNUMBER for RANS out of range' )
322  ENDIF
323 
324 #ifdef RFLO
325  IF (input%spaceDiscr /= rans_discr_cen .AND. &
326  input%spaceDiscr /= rans_discr_upw) THEN
327  CALL errorstop( global,err_turb_ransinput,__line__, &
328  'selected RaNS space discretization is not defined' )
329  ENDIF
330 #endif
331 #ifdef RFLU
332  IF (input%spaceDiscr /= rans_discr_upw) THEN
333  CALL errorstop( global,err_turb_ransinput,__line__, &
334  'selected RaNS space discretization is not defined in Rocflu' )
335  ENDIF
336 #endif
337 
338  IF (input%spaceOrder /= rans_discr_ord1 .AND. &
339  input%spaceOrder /= rans_discr_ord2) THEN
340  CALL errorstop( global,err_turb_ransinput,__line__, &
341  'selected RaNS space discretization order is not defined' )
342  ENDIF
343  ENDIF
344 
345 ! --- pertinent to WLM
346 
347 #ifdef RFLO
348  ilev = 1 ! check input based on finest level
349  CALL rflo_getdimensdummy( regions(ireg),ilev,idcbeg,idcend, &
350  jdcbeg,jdcend,kdcbeg,kdcend )
351 
352  DO ipatch=1,regions(ireg)%nPatches
353  patch1 => regions(ireg)%levels(ilev)%patches(ipatch)
354 #endif
355 #ifdef RFLU
356  DO ipatch=1,regions(ireg)%grid%nPatches
357  patch1 => regions(ireg)%patches(ipatch)
358 #endif
359  IF (patch1%bcType>=bc_noslipwall .AND. &
360  patch1%bcType<=bc_noslipwall+bc_range) THEN
361 
362  IF (patch1%valBola%nSwitches <= 0) THEN
363  CALL errorstop( global,err_turb_fixparam,__line__, &
364  'nSwitches in bcvalues type valBola should be > 0' )
365  ENDIF
366 
367  IF (patch1%valBola%switches(wlm_input_model) < 0 .OR. &
368  patch1%valBola%switches(wlm_input_model) > wlm_model_extern) THEN
369  CALL errorstop( global,err_turb_wlminput,__line__,'MODEL: 0-3' )
370  ENDIF
371 
372  IF (patch1%valBola%switches(wlm_input_model) == wlm_model_extern) THEN
373  CALL errorstop( global,err_turb_wlminput,__line__, &
374  'Ext. tau_wall not ready yet' )
375  ENDIF
376 
377  IF (patch1%valBola%switches(wlm_input_model)/=wlm_model_nomodel) THEN
378 
379  IF (minval(patch1%valBola%vals(:,wlm_vals_rough)) < 0._rfreal) THEN
380  CALL errorstop( global,err_turb_wlminput,__line__, &
381  'ROUGHNESS: > 0.0' )
382  ENDIF
383 #ifdef RFLO
384  IF (patch1%valBola%switches(wlm_input_refpoint) < 1) THEN
385  CALL errorstop( global,err_turb_wlminput,__line__, &
386  'WLM reference point should be >= 1' )
387  ENDIF
388  maxrange = idcend-idcbeg+ 1
389  IF ((patch1%lbound == 1 .OR. patch1%lbound == 2) .AND. &
390  patch1%valBola%switches(wlm_input_refpoint) > maxrange) THEN
391  CALL errorstop( global,err_turb_wlminput,__line__, &
392  'WLM reference point exceeds region max. range' )
393  ENDIF
394  maxrange = jdcend-jdcbeg+ 1
395  IF ((patch1%lbound == 3 .OR. patch1%lbound == 4) .AND. &
396  patch1%valBola%switches(wlm_input_refpoint) > maxrange) THEN
397  CALL errorstop( global,err_turb_wlminput,__line__, &
398  'WLM reference point exceeds region max. range' )
399  ENDIF
400  maxrange = kdcend-kdcbeg+ 1
401  IF ((patch1%lbound == 5 .OR. patch1%lbound == 6) .AND. &
402  patch1%valBola%switches(wlm_input_refpoint) > maxrange) THEN
403  CALL errorstop( global,err_turb_wlminput,__line__, &
404  'WLM reference point exceeds region max. range' )
405  ENDIF
406 #endif
407 #ifdef RFLU
408  CALL errorstop( global,err_turb_wlminput,__line__, &
409  'Wall Layer Model is not available yet in Rocflu' )
410 #endif
411  ENDIF ! switch
412  ENDIF ! bcType
413  ENDDO ! iPatch
414 
415 ! --- check turbulence statistics input
416 
417  IF (input%nSt > st_turb_nvar) THEN
418  CALL errorstop( global,err_turb_fixparam,__line__, &
419  'increase ST_TURB_NVAR in parameters module file' )
420  ENDIF
421 
422 #ifdef STATS
423  IF (global%turbNStat > (input%nFixSt+input%nSv+input%nSt)) THEN
424  CALL errorstop( global,err_turb_statsinput,__line__, &
425  'TURBNSTAT larger than allocated; nSv (stress), nSt (stats) may be 0' )
426  ENDIF
427 
428  IF ((global%doStat==1) .AND. &
429  (mixtinput%turbModel/=turb_model_dynsmag) .AND. &
430  (mixtinput%turbModel/=turb_model_dynmixd)) THEN
431  DO m = 1,global%turbNStat
432  IF (global%turbStatId(1,m)==0 .AND. global%turbStatId(2,m)>2 ) THEN
433  CALL errorstop( global,err_turb_statsinput,__line__, &
434  'TURBSTATID > 02 only for dyn.LES; chg setting if otherwise desired' )
435  ENDIF
436  ENDDO
437  ENDIF
438 #endif
439 
440 #ifdef RFLO
441  ENDIF ! region active
442 #endif
443  ENDDO ! iReg
444 
445 ! global checking --------------------------------------------------------
446 
447 #ifdef RFLO
448  DO ireg=1,global%nRegions ! serial process
449 #endif
450 #ifdef RFLU
451  DO ireg = lbound(regions,1),ubound(regions,1)
452 #endif
453  mixtinput => regions(ireg)%mixtInput
454  input => regions(ireg)%turbInput
455 
456 ! - general: turbInactive and moveGrid vs fixedGrid
457 
458  IF (mixtinput%turbModel == turb_model_none) THEN
459  turbinactive = .true.
460  ENDIF
461  IF (mixtinput%moveGrid .eqv. .true.) movegrid = .true.
462  IF (.NOT. (mixtinput%moveGrid .eqv. .true.)) fixedgrid = .true.
463 
464 ! - RaNS/DES: wRansActive and noNsWall
465 
466  IF (input%modelClass == model_rans) THEN
467  IF ((mixtinput%turbModel==turb_model_sa).OR. &
468  (mixtinput%turbModel==turb_model_dessa).OR. &
469  (mixtinput%turbModel==turb_model_hdessa)) THEN
470  wransactive = .true.
471  ENDIF
472  ENDIF
473 
474 # ifdef RFLO
475  DO ipatch=1,regions(ireg)%nPatches
476  patch1 => regions(ireg)%levels(ilev)%patches(ipatch)
477 #endif
478 # ifdef RFLU
479  DO ipatch=1,regions(ireg)%grid%nPatches
480  patch1 => regions(ireg)%patches(ipatch)
481 #endif
482  IF (patch1%bcType>=bc_noslipwall .AND. &
483  patch1%bcType<=bc_noslipwall+bc_range) THEN
484  nonswall = .false.
485  ENDIF
486  ENDDO
487 
488  ENDDO ! iReg
489 
490 #ifdef GENX
491  IF (turbinactive .eqv. .true.) THEN
492  CALL errorstop( global,err_turb_region,__line__, &
493  'For Genx, turbulence should be active in all regions or none at all' )
494  ENDIF
495 #endif
496  IF ((fixedgrid .eqv. .true.) .AND. (movegrid .eqv. .true.)) THEN
497  CALL errorstop( global,err_turb_input,__line__, &
498  'QUESTION: Is it safe to only update metrics in regions that move?' )
499  ENDIF
500 
501  IF ((wransactive .eqv. .true.) .AND. (nonswall .eqv. .true.)) THEN
502  CALL errorstop( global,err_turb_input,__line__, &
503  'RaNS model selected needs wall distance but no ns-wall presents' )
504  ENDIF
505 
506 ! finalize -------------------------------------------------------------------
507 
508  IF ( global%myProcid == masterproc .AND. &
509  global%verbLevel > verbose_none ) THEN
510  WRITE(stdout,'(A,1X,A)') solver_name,'Leaving TURB_CheckParamInput.'
511  END IF ! global%verbLevel
512 
513  CALL deregisterfunction( global )
514 
515 END SUBROUTINE turb_checkparaminput
516 
517 !******************************************************************************
518 !
519 ! RCS Revision history:
520 !
521 ! $Log: TURB_CheckParamInput.F90,v $
522 ! Revision 1.19 2009/08/26 12:28:52 mtcampbe
523 ! Ported to Hera. Fixed logical expression syntax errors. Replaced all
524 ! IF (logical_variable) with IF (logical_variable .eqv. .true.) as
525 ! consistent with the specification. Also changed: IF( ASSOCIATED(expr) )
526 ! to IF ( ASSOCIATED(expr) .eqv. .true. ). Intel compilers produce code
527 ! which silently fails for some mal-formed expressions, so these changes
528 ! are a net which should ensure that they are evaluated as intended.
529 !
530 ! Revision 1.18 2008/12/06 08:44:41 mtcampbe
531 ! Updated license.
532 !
533 ! Revision 1.17 2008/11/19 22:17:53 mtcampbe
534 ! Added Illinois Open Source License/Copyright
535 !
536 ! Revision 1.16 2006/02/04 05:00:18 wasistho
537 ! added enter and leave statements
538 !
539 ! Revision 1.15 2006/01/12 09:50:07 wasistho
540 ! enabled tripping fixed Smagorinsky
541 !
542 ! Revision 1.14 2005/12/29 19:47:14 wasistho
543 ! bug fixed start/end index of ireg for rflu
544 !
545 ! Revision 1.13 2005/03/09 06:34:45 wasistho
546 ! incorporated HDESSA
547 !
548 ! Revision 1.12 2005/03/08 01:54:56 wasistho
549 ! fixed bug, added if dostat cheking in turb-statistics
550 !
551 ! Revision 1.11 2004/12/10 01:03:13 wasistho
552 ! trap turbStatId error in connection with turbmodel selected
553 !
554 ! Revision 1.10 2004/08/12 20:58:39 wasistho
555 ! check roughness value only when WLM is active
556 !
557 ! Revision 1.9 2004/08/07 01:08:03 wasistho
558 ! error msg if Dyn.Mixed selected in Rocflu
559 !
560 ! Revision 1.8 2004/07/03 01:44:00 wasistho
561 ! removed restriction to only fixed Smag in Rocflu
562 !
563 ! Revision 1.7 2004/05/28 01:59:43 wasistho
564 ! update unstructured grid LES
565 !
566 ! Revision 1.6 2004/04/08 04:00:27 wasistho
567 ! allow DES with moving grid
568 !
569 ! Revision 1.5 2004/03/27 02:16:42 wasistho
570 ! compiled with Rocflu
571 !
572 ! Revision 1.4 2004/03/24 03:37:02 wasistho
573 ! prepared for RFLU
574 !
575 ! Revision 1.3 2004/03/20 03:28:29 wasistho
576 ! prepared for RFLU
577 !
578 ! Revision 1.2 2004/03/19 02:45:12 wasistho
579 ! prepared for RFLU
580 !
581 ! Revision 1.1 2004/03/05 21:08:02 wasistho
582 ! changed nomenclature
583 !
584 ! Revision 1.18 2004/02/26 21:25:50 wasistho
585 ! delete energy sgs warning
586 !
587 ! Revision 1.17 2004/02/24 21:03:23 wasistho
588 ! modified the warning previously checked in
589 !
590 ! Revision 1.16 2004/02/24 02:52:18 wasistho
591 ! added warning for unbalance load MPI if LES energy model is used
592 !
593 ! Revision 1.15 2004/02/19 04:03:42 wasistho
594 ! added new rans/SA parameter VISCFUNCTION
595 !
596 ! Revision 1.14 2004/02/14 03:43:07 wasistho
597 ! added new WLM parameter: reference point
598 !
599 ! Revision 1.13 2004/02/11 03:24:40 wasistho
600 ! added feature: variable number of turbulence output fields
601 !
602 ! Revision 1.12 2003/12/24 00:04:36 wasistho
603 ! modify WLM checking to satisfy Turing
604 !
605 ! Revision 1.11 2003/10/26 00:56:14 wasistho
606 ! bug fixed
607 !
608 ! Revision 1.10 2003/10/26 00:09:26 wasistho
609 ! added multiple discr.types and order
610 !
611 ! Revision 1.9 2003/10/07 02:05:04 wasistho
612 ! initial installation of RaNS-SA and DES
613 !
614 ! Revision 1.8 2003/09/11 03:07:30 wasistho
615 ! removed ASSOCIATED(patch1%valBola%switches)
616 !
617 ! Revision 1.7 2003/08/29 20:30:35 wasistho
618 ! Added check for vorticity computation in Genx
619 !
620 ! Revision 1.6 2003/08/06 15:56:05 wasistho
621 ! added vorticities computation
622 !
623 ! Revision 1.5 2003/07/18 20:12:56 wasistho
624 ! put ifdef STATS
625 !
626 ! Revision 1.4 2003/07/17 01:23:10 wasistho
627 ! prepared rocturb for Genx
628 !
629 ! Revision 1.3 2003/05/31 01:46:21 wasistho
630 ! installed turb. wall layer model
631 !
632 ! Revision 1.2 2003/05/24 02:11:05 wasistho
633 ! turbulence statistics expanded
634 !
635 ! Revision 1.1 2002/10/14 23:55:29 wasistho
636 ! Install Rocturb
637 !
638 !
639 !******************************************************************************
640 
641 
642 
643 
644 
645 
646 
FT m(int i, int j) const
**********************************************************************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
subroutine turb_checkparaminput(regions)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
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
subroutine input(X, NNODE, NDC, NCELL, NFCE, NBPTS, NBFACE, ITYP, NPROP, XBNDY, XFAR, YFAR, ZFAR)
**********************************************************************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
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE jdcend
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE jdcbeg
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469