62 TYPE(t_region
),
POINTER :: regions(:)
65 INTEGER :: ireg,
m, ipatch
68 CHARACTER(CHRLEN) :: rcsidentstring
73 TYPE(t_patch),
POINTER :: patch1
74 LOGICAL :: turbinactive, fixedgrid, movegrid, wransactive, nonswall
78 INTEGER :: ilev, maxrange
83 rcsidentstring =
'$RCSfile: TURB_CheckParamInput.F90,v $'
85 global => regions(1)%global
87 'TURB_CheckParamInput.F90' )
89 IF ( global%myProcid == masterproc .AND. &
90 global%verbLevel > verbose_none )
THEN
91 WRITE(stdout,
'(A,1X,A)') solver_name,
'Entering TURB_CheckParamInput...'
98 IF ((ycoord - xcoord)/=1 .OR. &
99 (zcoord - ycoord)/=1)
THEN
100 CALL
errorstop( global,err_turb_fixparam,__line__,
'XCOORD,YCOORD,ZCOORD' )
105 CALL
errorstop( global,err_turb_fixparam,__line__,
'NDIR /= 3' )
107 IF ((dirk-dirj /= 1).OR.(dirj-diri /= 1).OR.(diri /= 1))
THEN
108 CALL
errorstop( global,err_turb_fixparam,__line__,
'DIRI,DIRJ,DIRK' )
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_...' )
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_...' )
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_...' )
131 IF ((cv_turb_dens /= cv_mixt_dens) .OR. &
132 (cv_turb_xmom /= cv_mixt_xmom) .OR. &
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_...' )
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_...' )
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_...' )
168 turbinactive = .false.
171 wransactive = .false.
175 DO ireg = 1,global%nRegions
176 IF (regions(ireg)%procid==global%myProcid .AND. &
177 regions(ireg)%active==active)
THEN
180 DO ireg = lbound(regions,1),ubound(regions,1)
183 mixtinput => regions(ireg)%mixtInput
184 input => regions(ireg)%turbInput
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__ )
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' )
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' )
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' )
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' )
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' )
225 IF (
input%nZof > zof_nelm)
THEN
226 CALL
errorstop( global,err_turb_fixparam,__line__, &
227 'ZOF_NELM < input%nZof, increase the former' )
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
238 CALL
errorstop( global,err_turb_lesinput,__line__, &
239 'selected turbulence model is not of LES class' )
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' )
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' )
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' )
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' )
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' )
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' )
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' )
287 IF ((
input%engModel /= off) .AND. &
288 (
input%engModel /= active))
THEN
289 CALL
errorstop( global,err_turb_lesinput,__line__, &
290 'ENERGYMODEL: 0 or 1' )
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' )
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' )
315 CALL
errorstop( global,err_turb_ransinput,__line__, &
316 'selected turbulence model is not of RANS/DES class' )
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' )
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' )
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' )
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' )
352 DO ipatch=1,regions(ireg)%nPatches
353 patch1 => regions(ireg)%levels(ilev)%patches(ipatch)
356 DO ipatch=1,regions(ireg)%grid%nPatches
357 patch1 => regions(ireg)%patches(ipatch)
359 IF (patch1%bcType>=bc_noslipwall .AND. &
360 patch1%bcType<=bc_noslipwall+bc_range)
THEN
362 IF (patch1%valBola%nSwitches <= 0)
THEN
363 CALL
errorstop( global,err_turb_fixparam,__line__, &
364 'nSwitches in bcvalues type valBola should be > 0' )
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' )
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' )
377 IF (patch1%valBola%switches(wlm_input_model)/=wlm_model_nomodel)
THEN
379 IF (minval(patch1%valBola%vals(:,wlm_vals_rough)) < 0._rfreal)
THEN
380 CALL
errorstop( global,err_turb_wlminput,__line__, &
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' )
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' )
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' )
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' )
408 CALL
errorstop( global,err_turb_wlminput,__line__, &
409 'Wall Layer Model is not available yet in Rocflu' )
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' )
424 CALL
errorstop( global,err_turb_statsinput,__line__, &
425 'TURBNSTAT larger than allocated; nSv (stress), nSt (stats) may be 0' )
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' )
448 DO ireg=1,global%nRegions
451 DO ireg = lbound(regions,1),ubound(regions,1)
453 mixtinput => regions(ireg)%mixtInput
454 input => regions(ireg)%turbInput
458 IF (mixtinput%turbModel == turb_model_none)
THEN
459 turbinactive = .true.
461 IF (mixtinput%moveGrid .eqv. .true.) movegrid = .true.
462 IF (.NOT. (mixtinput%moveGrid .eqv. .true.)) fixedgrid = .true.
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
475 DO ipatch=1,regions(ireg)%nPatches
476 patch1 => regions(ireg)%levels(ilev)%patches(ipatch)
479 DO ipatch=1,regions(ireg)%grid%nPatches
480 patch1 => regions(ireg)%patches(ipatch)
482 IF (patch1%bcType>=bc_noslipwall .AND. &
483 patch1%bcType<=bc_noslipwall+bc_range)
THEN
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' )
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?' )
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' )
508 IF ( global%myProcid == masterproc .AND. &
509 global%verbLevel > verbose_none )
THEN
510 WRITE(stdout,
'(A,1X,A)') solver_name,
'Leaving TURB_CheckParamInput.'
**********************************************************************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 registerfunction(global, funName, fileName)
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)
subroutine deregisterfunction(global)