62   TYPE(t_region
), 
POINTER :: regions(:)
 
   69   CHARACTER(CHRLEN)           :: rcsidentstring
 
   70   TYPE(t_patch), 
POINTER      :: patch1
 
   74   TYPE(t_region
), 
POINTER     :: pregion
 
   80   rcsidentstring = 
'$RCSfile: TURB_InitInputValues.F90,v $' 
   82   global => regions(1)%global
 
   84   'TURB_InitInputValues.F90' )
 
   86   IF ( global%myProcid == masterproc .AND. &
 
   87        global%verbLevel > verbose_none ) 
THEN 
   88     WRITE(stdout,
'(A,1X,A)') solver_name,
'Entering TURB_InitInputValues...' 
   93   global%turbActive        = .false.
 
   94   global%turbCalcWDist     = .false.
 
   95   global%turbWorkUnused    = .true.
 
   96   global%turbWallDim       = 0
 
   97   global%turbCalcWDistFreq = calcwdist_ini
 
  102   DO ireg=1,global%nRegions
 
  106   IF (global%moduleType == module_type_solver) 
THEN 
  107     DO ireg = lbound(regions,1),ubound(regions,1)
 
  108       pregion => regions(ireg)
 
  114     DO ireg = lbound(regions,1),ubound(regions,1)
 
  115       regions(ireg)%grid%nPatches = 0
 
  120   DO ireg = lbound(regions,1),ubound(regions,1)
 
  123     input => regions(ireg)%turbInput
 
  128     input%modelClass     = model_none
 
  133     input%wDistMethod    = wdist_direct
 
  134     input%cDes           =  0.65_rfreal
 
  135     input%smoocf         = -1._rfreal
 
  136     input%spaceDiscr     = rans_discr_upw
 
  137     input%vis2           =  0.50_rfreal
 
  138     input%vis4           =  0._rfreal
 
  139     input%spaceOrder     = rans_discr_ord1
 
  140     input%functV1        = sa_fv1_pow3
 
  144     input%cSmag          = 0.1_rfreal
 
  145     input%xyzSmag(:)     = -huge( 1.0_rfreal )
 
  146     input%filterType     = filtype_uniform
 
  147     input%deltaType      = deltype_cbrt
 
  148     input%filterWidth(:) = filwidth_one
 
  149     input%homDir(:)      = off
 
  150     input%engModel       = active
 
  151     input%calcVort       = calcvort_no
 
  155     input%wallModel      = wlm_model_nomodel 
 
  156     input%wlmRefPoint    = 1                 
 
  162     DO ipatch=1,regions(ireg)%nPatches
 
  166       patch1 => regions(ireg)%levels(1)%patches(ipatch)
 
  168       patch1%turb%nData = 0                              
 
  169       patch1%turb%nSwitches = 0
 
  170       patch1%turb%distrib = bcdat_constant 
 
  172       patch1%valBola%bcSet = .false.   
 
  174       IF ((patch1%bcType>=bc_noslipwall .AND. &
 
  175            patch1%bcType<=bc_noslipwall+bc_range) .AND. &   
 
  176            regions(ireg)%procid==global%myProcid  .AND. &   
 
  177            regions(ireg)%active==active) 
THEN                
  180     DO ipatch=1,regions(ireg)%grid%nPatches     
 
  184       patch1 => regions(ireg)%patches(ipatch)   
 
  187       patch1%turb%nData = 0                         
 
  188       patch1%turb%nSwitches = 0                     
 
  189       patch1%turb%distrib = bcdat_constant          
 
  191       IF (patch1%bcType>=bc_noslipwall .AND. &
 
  192           patch1%bcType<=bc_noslipwall+bc_range) 
THEN   
  197         patch1%valBola%nData = 0
 
  198         patch1%valBola%nSwitches = 0
 
  199         patch1%valBola%distrib = bcdat_constant 
 
  200         patch1%valBola%nSwitches = patch1%valBola%nSwitches + wlm_nswitch
 
  202         ALLOCATE( patch1%valBola%switches(patch1%valBola%nSwitches), &
 
  204         global%error = errorflag
 
  205         IF (global%error /= 0) CALL 
errorstop( global,err_allocate,__line__ )
 
  209         patch1%valBola%switches(wlm_input_model)    = 
input%wallModel
 
  210         patch1%valBola%switches(wlm_input_refpoint) = 
input%wlmRefPoint
 
  221   IF ( global%myProcid == masterproc .AND. &
 
  222        global%verbLevel > verbose_none ) 
THEN 
  223     WRITE(stdout,
'(A,1X,A)') solver_name,
'Leaving TURB_InitInputValues.' 
subroutine rflu_creategrid(pRegion)
subroutine registerfunction(global, funName, fileName)
subroutine input(X, NNODE, NDC, NCELL, NFCE, NBPTS, NBFACE, ITYP, NPROP, XBNDY, XFAR, YFAR, ZFAR)
subroutine, public rflu_readdimensions(pRegion)
subroutine errorstop(global, errorCode, errorLine, addMessage)
subroutine deregisterfunction(global)