Ignore:
Timestamp:
Oct 16, 2017 12:41:56 PM (7 years ago)
Author:
schwenkel
Message:

extended by cloud_droplets option

File:
1 edited

Legend:

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

    r2508 r2547  
    2525! -----------------
    2626! $Id$
     27! extended by cloud_droplets option
     28!
     29! 2508 2017-10-02 08:57:09Z suehring
    2730! Minor formatting adjustment
    2831!
     
    139142       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0q       !< roughness length for humidity
    140143
    141        REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt1       !< Specific humidity at first grid level (required for cloud_physics = .T.)
    142        REAL(wp), DIMENSION(:), ALLOCATABLE ::  qv1       !< Potential temperature at first grid level (required for cloud_physics = .T.)
     144       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt1       !< Specific humidity at first grid level (required for cloud_physics = .T. or cloud_droplets = .T.)
     145       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qv1       !< Potential temperature at first grid level (required for cloud_physics = .T. or cloud_droplets = .T.)
    143146!
    144147!--    Define arrays for surface fluxes
     
    745748!--    When cloud physics is used, arrays for storing potential temperature and
    746749!--    specific humidity at first grid level are required.
    747        IF ( cloud_physics )  THEN
     750       IF ( cloud_physics  .OR.  cloud_droplets )  THEN
    748751          ALLOCATE ( surfaces%pt1(1:surfaces%ns) )
    749752          ALLOCATE ( surfaces%qv1(1:surfaces%ns) )
Note: See TracChangeset for help on using the changeset viewer.