Ignore:
Timestamp:
May 9, 2018 8:42:38 AM (6 years ago)
Author:
maronga
Message:

series of bugfixes

File:
1 edited

Legend:

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

    r3004 r3014  
    2525! -----------------
    2626! $Id$
     27! Bugfix: set some initial values
     28! Bugfix: domain bounds of local_pf corrected
     29!
     30! 3004 2018-04-27 12:33:25Z Giersch
    2731! Further allocation checks implemented (averaged data will be assigned to fill
    2832! values if no allocation happened so far)
     
    46394643       surf_lsm_h%pavement_surface     = .FALSE.
    46404644       surf_lsm_h%vegetation_surface   = .FALSE.
     4645
     4646!
     4647!--    Set default values
     4648       surf_lsm_h%r_canopy_min = 0.0_wp
     4649
    46414650!
    46424651!--    Vertical surfaces
     
    46714680          surf_lsm_v(l)%vegetation_surface   = .FALSE.
    46724681         
     4682
     4683!
     4684!--       Set default values
     4685          surf_lsm_v(l)%r_canopy_min = 0.0_wp
     4686       
    46734687       ENDDO
    46744688
     
    56325646    REAL(wp) ::  fill_value = -999.0_wp    !< value for the _FillValue attribute
    56335647
    5634     REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb:nzt+1) ::  local_pf !<
     5648    REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
    56355649
    56365650
Note: See TracChangeset for help on using the changeset viewer.