modsubgriddata.f90 Source File


Files dependent on this one

sourcefile~~modsubgriddata.f90~~AfferentGraph sourcefile~modsubgriddata.f90 modsubgriddata.f90 sourcefile~advection.f90 advection.f90 sourcefile~advection.f90->sourcefile~modsubgriddata.f90 sourcefile~modboundary.f90 modboundary.f90 sourcefile~modboundary.f90->sourcefile~modsubgriddata.f90 sourcefile~moddriver.f90 moddriver.f90 sourcefile~modboundary.f90->sourcefile~moddriver.f90 sourcefile~modinlet.f90 modinlet.f90 sourcefile~modboundary.f90->sourcefile~modinlet.f90 sourcefile~modchecksim.f90 modchecksim.f90 sourcefile~modchecksim.f90->sourcefile~modsubgriddata.f90 sourcefile~modibm.f90 modibm.f90 sourcefile~modibm.f90->sourcefile~modsubgriddata.f90 sourcefile~modsave.f90 modsave.f90 sourcefile~modsave.f90->sourcefile~modsubgriddata.f90 sourcefile~modstartup.f90 modstartup.f90 sourcefile~modstartup.f90->sourcefile~modsubgriddata.f90 sourcefile~modstartup.f90->sourcefile~modboundary.f90 sourcefile~modsubgrid.f90 modsubgrid.f90 sourcefile~modstartup.f90->sourcefile~modsubgrid.f90 sourcefile~modstartup.f90->sourcefile~moddriver.f90 sourcefile~modstartup.f90->sourcefile~modinlet.f90 sourcefile~modpois.f90 modpois.f90 sourcefile~modstartup.f90->sourcefile~modpois.f90 sourcefile~modstatistics.f90 modstatistics.f90 sourcefile~modstatistics.f90->sourcefile~modsubgriddata.f90 sourcefile~modsubgrid.f90->sourcefile~modsubgriddata.f90 sourcefile~modsubgrid.f90->sourcefile~modboundary.f90 sourcefile~tstep.f90 tstep.f90 sourcefile~tstep.f90->sourcefile~modsubgriddata.f90 sourcefile~wf_gr.f90 wf_gr.f90 sourcefile~wf_gr.f90->sourcefile~modsubgriddata.f90 sourcefile~wf_uno.f90 wf_uno.f90 sourcefile~wf_uno.f90->sourcefile~modsubgriddata.f90 sourcefile~wfmneutral.f90 wfmneutral.f90 sourcefile~wfmneutral.f90->sourcefile~modsubgriddata.f90 sourcefile~advec_2nd.f90 advec_2nd.f90 sourcefile~advec_2nd.f90->sourcefile~modibm.f90 sourcefile~moddriver.f90->sourcefile~modsave.f90 sourcefile~modinlet.f90->sourcefile~modsave.f90 sourcefile~modpois.f90->sourcefile~modboundary.f90 sourcefile~modstatsdump.f90 modstatsdump.f90 sourcefile~modstatsdump.f90->sourcefile~modstatistics.f90 sourcefile~modstatsdump.f90->sourcefile~modsubgrid.f90 sourcefile~program.f90 program.f90 sourcefile~program.f90->sourcefile~modboundary.f90 sourcefile~program.f90->sourcefile~modchecksim.f90 sourcefile~program.f90->sourcefile~modibm.f90 sourcefile~program.f90->sourcefile~modsave.f90 sourcefile~program.f90->sourcefile~modstartup.f90 sourcefile~program.f90->sourcefile~modsubgrid.f90 sourcefile~program.f90->sourcefile~modpois.f90 sourcefile~program.f90->sourcefile~modstatsdump.f90

Contents

Source Code


Source Code

!!> \file modsubdata.f90
!!!  Provides variable definitions for Calculates and applies the Sub Filter Scale diffusion
!
!>
!!  Calculates and applies the Sub Filter Scale diffusion
!>
!!  \author Jasper Tomas, TU Delft
!!  \author Pier Siebesma, K.N.M.I.
!!  \author Stephan de Roode,TU Delft
!!  \author Chiel van Heerwaarden, Wageningen U.R.
!!  \author Thijs Heus,MPI-M
!!  \par Revision list
!!  \todo Documentation
!
!  This file is part of DALES.
!
! DALES is free software; you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation; either version 3 of the License, or
! (at your option) any later version.
!
! DALES is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
! GNU General Public License for more details.
!
! You should have received a copy of the GNU General Public License
! along with this program.  If not, see <http://www.gnu.org/licenses/>.
!
!  Copyright 1993-2009 Delft University of Technology, Wageningen University, Utrecht University, KNMI
!

module modsubgriddata
implicit none
save
! private
  logical :: ldelta       = .false. !<  switch for subgrid length formulation (on/off)
  logical :: lmason       = .false. !<  switch for decreased length scale near the surface
  logical :: lsmagorinsky = .false. !<  switch for smagorinsky subgrid scheme
  logical :: lvreman      = .false. !<  switch for Vreman (2004) subgrid scheme
  logical :: lbuoycorr    = .false. !<  switch for buoyancy correction in Vreman (2004) subgrid scheme
  logical :: loneeqn      = .false. !<  switch for one-eqn subgrid scheme
  real :: cf      = 2.5  !< filter constant
  real :: Rigc    = 0.25 !< critical Richardson number
  real :: Prandtl = 0.333
!  real :: Prandtl = 3.0
!  real :: prandtli= 1./3.
  real :: prandtli
  real :: cm      = 0.12
  real :: cn      = 0.76
  real :: ch1     = 1.
  real :: ch2     = 2.
  real :: ce1     = 0.19
  real :: ce2     = 0.51
  real :: cs      = -1.
  real :: nmason  = 2.   !< exponent in Mason correction function
  real :: alpha_kolm  = 1.5     !< factor in Kolmogorov expression for spectral energy
  real :: beta_kolm   = 1.      !< factor in Kolmogorov relation for temperature spectrum
!  real :: damp   = 1.      !< used in van driest damping function
  real :: dampmin   = 1e-10     !< maximum damping used in van driest/Piomelli damping function
  real :: c_vreman  = 0.07      !< model constant for subgrid-scale model by Vreman (2004)        
!  real :: c_vreman  = 0.025      !< model constant for subgrid-scale model by Vreman (2004) corresponds with smag_const=0.1       

  real, allocatable :: ekm(:,:,:)   !< k-coefficient for momentum
  real, allocatable :: ekh(:,:,:)   !< k-coefficient for heat and q_tot

  real, allocatable :: sbdiss(:,:,:)!< dissiation
  real, allocatable :: sbshr(:,:,:) !< shear production
  real, allocatable :: sbbuo(:,:,:) !< buoyancy production / destruction
  real, allocatable :: zlt(:,:,:)   !< filter width
  
  real, allocatable :: csz(:,:)       !< Smagorinsky constant
  real, allocatable :: damp(:,:,:)      !< used in van Driest/Piomelli damping function
end module modsubgriddata