Ignore:
Timestamp:
Jan 18, 2021 11:15:37 AM (3 years ago)
Author:
raasch
Message:

maximum phase velocities are alwasy used for radiation boundary conditions, parameter use_cmax removed

File:
1 edited

Legend:

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

    r4828 r4845  
    2424! -----------------
    2525! $Id$
     26! -use_cmax and arrays required for radiation boundary conditions
     27!
     28! 4828 2021-01-05 11:21:41Z Giersch
    2629! file re-formatted to follow the PALM coding standard
    2730!
     
    216219    USE kinds
    217220
    218     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m                           !< mean phase velocity at outflow for u-component used
    219                                                                             !< in radiation boundary condition
    220     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_u_m_l                         !< mean phase velocity at outflow for u-component used
    221                                                                             !< in radiation boundary condition (local subdomain value)
    222     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m                           !< mean phase velocity at outflow for v-component used
    223                                                                             !< in radiation boundary condition
    224     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_v_m_l                         !< mean phase velocity at outflow for v-component used
    225                                                                             !< in radiation boundary condition (local subdomain value)
    226     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m                           !< mean phase velocity at outflow for w-component used
    227                                                                             !< in radiation boundary condition
    228     REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_w_m_l                         !< mean phase velocity at outflow for w-component used
    229                                                                             !< in radiation boundary condition (local subdomain value)
    230221    REAL(wp), DIMENSION(:), ALLOCATABLE ::  d_exner                         !< ratio of potential and actual temperature
    231222    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ddzu                            !< 1/dzu
     
    454445    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tric        !< coefficients of the tridiagonal matrix for solution of the Poisson
    455446                                                            !< equation in Fourier space
    456     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_l       !< velocity data (u at left boundary) from time level t-dt required for
    457                                                             !< radiation boundary condition
    458     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_n       !< velocity data (u at north boundary) from time level t-dt required for
    459                                                             !< radiation boundary condition
    460     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_r       !< velocity data (u at right boundary) from time level t-dt required for
    461                                                             !< radiation boundary condition
    462     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_m_s       !< velocity data (u at south boundary) from time level t-dt required for
    463                                                             !< radiation boundary condition
    464     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_l       !< velocity data (v at left boundary) from time level t-dt required for
    465                                                             !< radiation boundary condition
    466     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_n       !< velocity data (v at north boundary) from time level t-dt required for
    467                                                             !< radiation boundary condition
    468     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_r       !< velocity data (v at right boundary) from time level t-dt required for
    469                                                             !< radiation boundary condition
    470     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_m_s       !< velocity data (v at south boundary) from time level t-dt required for
    471                                                             !< radiation boundary condition
    472     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_l       !< velocity data (w at left boundary) from time level t-dt required for
    473                                                             !< radiation boundary condition
    474     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_n       !< velocity data (w at north boundary) from time level t-dt required for
    475                                                             !< radiation boundary condition
    476     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_r       !< velocity data (w at right boundary) from time level t-dt required for
    477                                                             !< radiation boundary condition
    478     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_m_s       !< velocity data (w at south boundary) from time level t-dt required for
    479                                                             !< radiation boundary condition
    480447
    481448    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  diss_1  !< pointer for swapping of timelevels for respective quantity
     
    10441011    LOGICAL ::  turbulent_outflow = .FALSE.                      !< namelist parameter
    10451012    LOGICAL ::  urban_surface = .FALSE.                          !< use urban surface model?
    1046     LOGICAL ::  use_cmax = .TRUE.                                !< namelist parameter
    10471013    LOGICAL ::  use_fixed_date = .FALSE.                         !< date of simulation does not change (namelist parameter)
    10481014    LOGICAL ::  use_fixed_time = .FALSE.                         !< time of simulation does not change (namelist parameter)
Note: See TracChangeset for help on using the changeset viewer.