Ignore:
Timestamp:
Oct 7, 2019 1:29:08 PM (4 years ago)
Author:
suehring
Message:

Land-surface model: Revise limitation for soil moisture in case it exceeds its saturation value; Revise initialization of soil moisture and temperature in a nested run in case dynamic input information is available. This case, the soil within the child domains can be initialized separately; As part of this revision, migrate the netcdf input of soil temperature / moisture to this module, as well as the routine to inter/extrapolate soil profiles between different grids.; Plant-canopy: Check if any LAD is prescribed when plant-canopy model is applied, in order to avoid crashes in the radiation transfer model; Surface-layer fluxes: Initialization of Obukhov length also at vertical surfaces (if allocated); Urban-surface model: Add checks to ensure that relative fractions of walls, windowns and green surfaces sum-u to one; Revise message calls dealing with local checks

File:
1 edited

Legend:

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

    r4237 r4258  
    2626! -----------------
    2727! $Id$
     28! Initialization of Obukhov lenght also at vertical surfaces (if allocated).
     29!
     30! 4237 2019-09-25 11:33:42Z knoop
    2831! Added missing OpenMP directives
    2932!
     
    554557! Description:
    555558! ------------
    556 !> Initializing actions for the surface layer routine. Basically, this involves
    557 !> the preparation of a lookup table for the the bulk Richardson number vs
    558 !> Obukhov length L when using the lookup table method.
     559!> Initializing actions for the surface layer routine.
    559560!------------------------------------------------------------------------------!
    560561    SUBROUTINE init_surface_layer_fluxes
     
    562563       IMPLICIT NONE
    563564
     565       INTEGER(iwp) ::  l  !< running index for vertical surface orientation
    564566
    565567       CALL location_message( 'initializing surface layer', 'start' )
     
    572574          IF ( surf_lsm_h%ns    >= 1 )  surf_lsm_h%ol    = 1.0E10_wp
    573575          IF ( surf_usm_h%ns    >= 1 )  surf_usm_h%ol    = 1.0E10_wp
     576         
     577          DO  l = 0, 3
     578             IF ( surf_def_v(l)%ns >= 1  .AND.                                 &
     579                  ALLOCATED( surf_def_v(l)%ol ) )  surf_def_v(l)%ol = 1.0E10_wp
     580             IF ( surf_lsm_v(l)%ns >= 1  .AND.                                 &
     581                  ALLOCATED( surf_lsm_v(l)%ol ) )  surf_lsm_v(l)%ol = 1.0E10_wp
     582             IF ( surf_usm_v(l)%ns >= 1  .AND.                                 &
     583                  ALLOCATED( surf_usm_v(l)%ol ) )  surf_usm_v(l)%ol = 1.0E10_wp 
     584          ENDDO
     585         
    574586       ENDIF
    575587
Note: See TracChangeset for help on using the changeset viewer.