Ignore:
Timestamp:
Jun 29, 2017 10:14:38 AM (7 years ago)
Author:
maronga
Message:

improvements for spinup mechanism

File:
1 edited

Legend:

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

    r2298 r2299  
    2525! -----------------
    2626! $Id$
     27! Removed pt_p from USE statement. Adjusted call to lsm_soil_model to allow
     28! spinups without soil moisture prediction
     29!
     30! 2298 2017-06-29 09:28:18Z raasch
    2731! type of write_binary changed from CHARACTER to LOGICAL
    2832!
     
    228232 
    229233    USE arrays_3d,                                                             &
    230         ONLY:  hyp, pt, pt_p, prr, q, q_p, ql, vpt, u, v, w
     234        ONLY:  hyp, pt, prr, q, q_p, ql, vpt, u, v, w
    231235
    232236    USE cloud_parameters,                                                      &
     
    28842888!> temperature and water content.
    28852889!------------------------------------------------------------------------------!
    2886     SUBROUTINE lsm_soil_model( horizontal, l )
     2890    SUBROUTINE lsm_soil_model( horizontal, l, calc_soil_moisture )
    28872891
    28882892
     
    28922896       INTEGER(iwp) ::  l       !< surface-data type index indication facing
    28932897       INTEGER(iwp) ::  m       !< running index
     2898
     2899       LOGICAL, INTENT(IN) ::  calc_soil_moisture !< flag indicating whether soil moisture shall be calculated or not.
    28942900
    28952901       LOGICAL      ::  horizontal !< flag indication horizontal wall, required to set pointer accordingly
     
    30593065
    30603066             ENDDO
     3067
     3068          ENDIF
     3069
     3070       ENDDO
     3071
     3072
     3073       DO  m = 1, surf%ns
     3074
     3075          IF (  .NOT.  surf%water_surface(m)  .AND.  calc_soil_moisture )  THEN
     3076
    30613077
    30623078!
Note: See TracChangeset for help on using the changeset viewer.