Ignore:
Timestamp:
Aug 20, 2019 11:55:33 AM (5 years ago)
Author:
oliver.maas
Message:

Added optional method for recycling of absolute values of pt and q instead of recycling only the deviations from the mean profile at the recycling plane. With the new method two problems are solved: 1. A horizontally homogeneous temperature and humidity field is achieved, even for non-neutral boundary layers and thus no thermal circulation is triggered. 2. No gravity waves build up at the inflow due to cyclic boundary conditions for pt and q.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/modules.f90

    r4168 r4172  
    2525! -----------------
    2626! $Id$
     27! added recycle_absolute_quantities and raq
     28!
     29! 4168 2019-08-16 13:50:17Z suehring
    2730! +topo_top_ind
    2831!
     
    11971200    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do2d = ' '  !< label array for 2d output quantities
    11981201    CHARACTER (LEN=varnamelength), DIMENSION(0:1,500) ::  do3d = ' '  !< label array for 3d output quantities
    1199 
     1202     
     1203    CHARACTER (LEN=varnamelength), DIMENSION(7) :: recycle_absolute_quantities = ' '    !< namelist parameter
     1204   
    12001205    INTEGER(iwp), PARAMETER ::  fl_max = 500     !< maximum number of virtual-flight measurements
    12011206    INTEGER(iwp), PARAMETER ::  var_fl_max = 20  !< maximum number of different sampling variables in virtual flight measurements
     
    13131318
    13141319    INTEGER(iwp), DIMENSION(max_masks,mask_xyz_dimension) ::  mask_k_over_surface = -1  !< namelist parameter, k index of height over surface
    1315 
     1320   
    13161321    LOGICAL ::  agent_time_unlimited = .FALSE.                   !< namelist parameter
    13171322    LOGICAL ::  air_chemistry = .FALSE.                          !< chemistry model switch
     
    14311436    LOGICAL ::  data_output_yz(0:1) = .FALSE.                !< output of yz cross-section data?
    14321437
    1433     LOGICAL, DIMENSION(max_masks) ::  mask_surface = .FALSE.      !< flag for surface-following masked output
    1434 
     1438    LOGICAL, DIMENSION(max_masks) ::  mask_surface = .FALSE.   !< flag for surface-following masked output
     1439   
     1440    LOGICAL, DIMENSION(7) ::  raq = .FALSE.                    !< recycle absolute quantities (u,v,w,theta,e,q,s) in inflow_turbulence
     1441   
    14351442    REAL(wp) ::  advected_distance_x = 0.0_wp                  !< advected distance of model domain along x
    14361443                                                               !< (galilei transformation)
Note: See TracChangeset for help on using the changeset viewer.