Ignore:
Timestamp:
Aug 7, 2017 8:59:53 AM (7 years ago)
Author:
gronemeier
Message:

changes to the 1D model

File:
1 edited

Legend:

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

    r2326 r2337  
    2525! -----------------
    2626! $Id$
     27! -old_dt_1d
     28! +l1d_diss
     29!
     30! 2326 2017-08-01 07:23:24Z gronemeier
    2731! Updated variable descriptions
    2832!
     
    17571761    REAL(wp) ::  dt_run_control_1d = 60.0_wp   !< namelist parameter
    17581762    REAL(wp) ::  end_time_1d = 864000.0_wp     !< namelist parameter
    1759     REAL(wp) ::  old_dt_1d = 1.0E-10_wp        !< previous timestep (1d-model)
    17601763    REAL(wp) ::  qs1d                          !< characteristic humidity scale (1d-model)
    17611764    REAL(wp) ::  simulated_time_1d = 0.0_wp    !< updated simulated time (1d-model)
     
    17751778    REAL(wp), DIMENSION(:), ALLOCATABLE ::  km1d     !< turbulent diffusion coefficient for momentum (1d-model)
    17761779    REAL(wp), DIMENSION(:), ALLOCATABLE ::  l_black  !< mixing length Blackadar (1d-model)
    1777     REAL(wp), DIMENSION(:), ALLOCATABLE ::  l1d      !< mixing length (1d-model)
     1780    REAL(wp), DIMENSION(:), ALLOCATABLE ::  l1d      !< mixing length for turbulent diffusion coefficients (1d-model)
     1781    REAL(wp), DIMENSION(:), ALLOCATABLE ::  l1d_diss !< mixing length for dissipation (1d-model)
    17781782    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rif1d    !< Richardson flux number (1d-model)
    17791783    REAL(wp), DIMENSION(:), ALLOCATABLE ::  te_e     !< tendency of e (1d-model)
Note: See TracChangeset for help on using the changeset viewer.