Ignore:
Timestamp:
Sep 9, 2020 8:27:58 PM (4 years ago)
Author:
pavelkrc
Message:

Radiative transfer model RTM version 4.1

File:
1 edited

Legend:

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

    r4598 r4671  
    2525! -----------------
    2626! $Id$
     27! Implementation of downward facing USM and LSM surfaces
     28!
     29! 4598 2020-07-10 10:13:23Z suehring
    2730! Revise surface-element mapping in mpi-io restart branch
    2831!
     
    543546    TYPE (surf_type), DIMENSION(0:2), TARGET ::  surf_def_h  !< horizontal default surfaces (Up, Down, and Top)
    544547    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_def_v  !< vertical default surfaces (North, South, East, West)
    545     TYPE (surf_type)                , TARGET ::  surf_lsm_h  !< horizontal natural land surfaces, so far only upward-facing
     548    TYPE (surf_type), DIMENSION(0:1), TARGET ::  surf_lsm_h  !< horizontal natural land surfaces (Up, Down)
    546549    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_lsm_v  !< vertical land surfaces (North, South, East, West)
    547     TYPE (surf_type)                , TARGET ::  surf_usm_h  !< horizontal urban surfaces, so far only upward-facing
     550    TYPE (surf_type), DIMENSION(0:1), TARGET ::  surf_usm_h  !< horizontal urban surfaces (Up, Down)
    548551    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_usm_v  !< vertical urban surfaces (North, South, East, West)
    549552
     
    855858    INTEGER(iwp) ::  k         !< running index z-direction
    856859    INTEGER(iwp) ::  l         !< index variable for surface facing
    857     INTEGER(iwp) ::  num_lsm_h !< number of horizontally-aligned natural surfaces
    858     INTEGER(iwp) ::  num_usm_h !< number of horizontally-aligned urban surfaces
     860    INTEGER(iwp) ::  kk        !< auxiliary index z-direction
     861    INTEGER(iwp) ::  kd        !< direction index
    859862
    860863    INTEGER(iwp), DIMENSION(0:2) ::  num_def_h !< number of horizontally-aligned default surfaces
     864    INTEGER(iwp), DIMENSION(0:1) ::  num_lsm_h !< number of horizontally-aligned natural surfaces
     865    INTEGER(iwp), DIMENSION(0:1) ::  num_usm_h !< number of horizontally-aligned urban surfaces
    861866    INTEGER(iwp), DIMENSION(0:3) ::  num_def_v !< number of vertically-aligned default surfaces
    862867    INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v !< number of vertically-aligned natural surfaces
     
    891896             IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
    892897!
    893 !--             Check if grid point adjoins to any upward-facing horizontal surface, e.g. the Earth
    894 !--             surface, plane roofs, or ceilings.
    895 
    896                 IF ( .NOT. BTEST( wall_flags_total_0(k-1,j,i), 0 ) )  THEN
    897 !
    898 !--                Determine flags indicating a terrain surface, a building surface,
    899                    terrain  = BTEST( wall_flags_total_0(k-1,j,i), 5 )  .OR.  topo_no_distinct
    900                    building = BTEST( wall_flags_total_0(k-1,j,i), 6 )  .OR.  topo_no_distinct
    901 !
    902 !--                Unresolved_building indicates a surface with equal height as terrain but with a
    903 !--                non-grid resolved building on top. These surfaces will be flagged as urban
    904 !--                surfaces.
    905                    unresolved_building = BTEST( wall_flags_total_0(k-1,j,i), 5 )  .AND.            &
    906                                          BTEST( wall_flags_total_0(k-1,j,i), 6 )
    907 !
    908 !--                Land-surface type
    909                    IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
    910                       num_lsm_h    = num_lsm_h    + 1
    911 !
    912 !--                Urban surface tpye
    913                    ELSEIF ( urban_surface  .AND.  building )  THEN
    914                       num_usm_h = num_usm_h + 1
    915 !
    916 !--                Default-surface type
    917                    ELSEIF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
    918                       num_def_h(0) = num_def_h(0) + 1
    919 !
    920 !--                Unclassifified surface-grid point. Give error message.
     898!--             Check if grid point adjoins to any upward- and downward-facing horizontal surface,
     899!--             e.g. the Earth surface, plane roofs, or ceilings.
     900                DO kk = k-1, k+1, 2
     901!
     902!--                Check for top-fluxes
     903                   IF ( kk == nzt+1  .AND.  use_top_fluxes )  THEN
     904                      num_def_h(2) = num_def_h(2) + 1
    921905                   ELSE
    922                       WRITE( message_string, * ) 'Unclassified upward-facing surface element '//   &
    923                                                  'at grid point (k,j,i) = ', k, j, i
    924                       CALL message( 'surface_mod', 'PA0698', 1, 2, myid, 6, 0 )
     906!
     907!--                   set direction index of the potential surface
     908                      kd = MERGE( 0, 1, kk == k-1 )
     909!
     910!--                   test the adjacent grid cell
     911                      IF ( .NOT. BTEST( wall_flags_total_0(kk,j,i), 0 ) )  THEN
     912!
     913!--                      Determine flags indicating a terrain surface, a building surface,
     914                         terrain  = BTEST( wall_flags_total_0(kk,j,i), 5 )  .OR.  topo_no_distinct
     915                         building = BTEST( wall_flags_total_0(kk,j,i), 6 )  .OR.  topo_no_distinct
     916!
     917!--                      Unresolved_building indicates a surface with equal height as terrain but with a
     918!--                      non-grid resolved building on top. These surfaces will be flagged as urban
     919!--                      surfaces.
     920                         unresolved_building = BTEST( wall_flags_total_0(kk,j,i), 5 )  .AND.            &
     921                                               BTEST( wall_flags_total_0(kk,j,i), 6 )
     922!
     923!--                      Land-surface type
     924                         IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
     925                            num_lsm_h(kd)    = num_lsm_h(kd)    + 1
     926!
     927!--                      Urban surface tpye
     928                         ELSEIF ( urban_surface  .AND.  building )  THEN
     929                            num_usm_h(kd) = num_usm_h(kd) + 1
     930!
     931!--                      Default-surface type
     932                         ELSEIF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
     933                            num_def_h(kd) = num_def_h(kd) + 1
     934!
     935!--                      Unclassifified surface-grid point. Give error message.
     936                         ELSE
     937                            WRITE( message_string, * ) 'Unclassified ',                            &
     938                                  TRIM(MERGE('  upward','downward',kk==0)),                        &
     939                                  '-facing surface element at grid point (k,j,i) = ', k, j, i
     940                            CALL message( 'surface_mod', 'PA0698', 1, 2, myid, 6, 0 )
     941                         ENDIF
     942                      ENDIF
    925943                   ENDIF
    926 
    927                 ENDIF
    928 !
    929 !--             Check for top-fluxes
    930                 IF ( k == nzt  .AND.  use_top_fluxes )  THEN
    931                    num_def_h(2) = num_def_h(2) + 1
    932 !
    933 !--             Check for any other downward-facing surface. So far only for default surface type.
    934                 ELSEIF ( .NOT. BTEST( wall_flags_total_0(k+1,j,i), 0 ) )  THEN
    935                    num_def_h(1) = num_def_h(1) + 1
    936                 ENDIF
    937 
     944                ENDDO
    938945             ENDIF
    939946          ENDDO
     
    10751082    surf_def_h(2)%ns = num_def_h(2)
    10761083!
    1077 !-- Horizontal surface, natural type, so far only upward-facing
    1078     surf_lsm_h%ns    = num_lsm_h
    1079 !
    1080 !-- Horizontal surface, urban type, so far only upward-facing
    1081     surf_usm_h%ns    = num_usm_h
     1084!-- Horizontal surface, natural type, upward facing
     1085    surf_lsm_h(0)%ns    = num_lsm_h(0)
     1086!
     1087!-- Horizontal surface, natural type, downward facing
     1088    surf_lsm_h(1)%ns    = num_lsm_h(1)
     1089!
     1090!-- Horizontal surface, urban type, upward facing
     1091    surf_usm_h(0)%ns    = num_usm_h(0)
     1092!
     1093!-- Horizontal surface, urban type, downward facing
     1094    surf_usm_h(1)%ns    = num_usm_h(1)
    10821095!
    10831096!-- Vertical surface, default type, northward facing
     
    11271140!
    11281141!-- Allocate required attributes for horizontal surfaces - natural type.
    1129     CALL allocate_surface_attributes_h ( surf_lsm_h, nys, nyn, nxl, nxr )
     1142    DO  l = 0, 1
     1143       CALL allocate_surface_attributes_h ( surf_lsm_h(l), nys, nyn, nxl, nxr )
     1144    ENDDO
    11301145!
    11311146!-- Allocate required attributes for horizontal surfaces - urban type.
    1132     CALL allocate_surface_attributes_h ( surf_usm_h, nys, nyn, nxl, nxr )
     1147    DO  l = 0, 1
     1148       CALL allocate_surface_attributes_h ( surf_usm_h(l), nys, nyn, nxl, nxr )
     1149    ENDDO
    11331150
    11341151!
     
    11821199    !$ACC COPYIN(surf_def_h(0:2)) &
    11831200    !$ACC COPYIN(surf_def_v(0:3)) &
    1184     !$ACC COPYIN(surf_lsm_h) &
     1201    !$ACC COPYIN(surf_lsm_h(0:1)) &
    11851202    !$ACC COPYIN(surf_lsm_v(0:3)) &
    1186     !$ACC COPYIN(surf_usm_h) &
     1203    !$ACC COPYIN(surf_usm_h(0:1)) &
    11871204    !$ACC COPYIN(surf_usm_v(0:3))
    11881205!
     
    11991216!
    12001217!-- Copy data in surf_lsm_h
    1201     CALL enter_surface_attributes_h( surf_lsm_h )
     1218    DO  l = 0, 1
     1219       CALL enter_surface_attributes_h( surf_lsm_h(l) )
     1220    ENDDO
    12021221!
    12031222!-- Copy data in surf_lsm_v(0:3)
     
    12071226!
    12081227!-- Copy data in surf_usm_h
    1209     CALL enter_surface_attributes_h( surf_usm_h )
     1228    DO  l = 0, 1
     1229       CALL enter_surface_attributes_h( surf_usm_h(l) )
     1230    ENDDO
    12101231!
    12111232!-- Copy data in surf_usm_v(0:3)
     
    12411262!
    12421263!-- Delete data in surf_lsm_h
    1243     CALL exit_surface_attributes_h( surf_lsm_h )
     1264    DO  l = 0, 1
     1265       CALL exit_surface_attributes_h( surf_lsm_h(l) )
     1266    ENDDO
    12441267!
    12451268!-- Delete data in surf_lsm_v(0:3)
     
    12491272!
    12501273!-- Delete data in surf_usm_h
    1251     CALL exit_surface_attributes_h( surf_usm_h )
     1274    DO  l = 0, 1
     1275       CALL exit_surface_attributes_h( surf_usm_h(l) )
     1276    ENDDO
    12521277!
    12531278!-- Delete data in surf_usm_v(0:3)
     
    12591284    !$ACC DELETE(surf_def_h(0:2)) &
    12601285    !$ACC DELETE(surf_def_v(0:3)) &
    1261     !$ACC DELETE(surf_lsm_h) &
     1286    !$ACC DELETE(surf_lsm_h(0:1)) &
    12621287    !$ACC DELETE(surf_lsm_v(0:3)) &
    1263     !$ACC DELETE(surf_usm_h) &
     1288    !$ACC DELETE(surf_usm_h(0:1)) &
    12641289    !$ACC DELETE(surf_usm_v(0:3))
    12651290
     
    21782203    INTEGER(iwp) ::  j  !< running index y-direction
    21792204    INTEGER(iwp) ::  k  !< running index z-direction
    2180 
    2181     INTEGER(iwp)  ::  start_index_lsm_h  !< dummy to determing local start index in surface type for given (j,i), for horizontal
    2182                                          !< natural surfaces
    2183     INTEGER(iwp)  ::  start_index_usm_h  !< dummy to determing local start index in surface type for given (j,i), for horizontal
    2184                                          !< urban surfaces
    2185 
    2186     INTEGER(iwp)  ::  num_lsm_h      !< current number of horizontal surface element, natural type
    2187     INTEGER(iwp)  ::  num_lsm_h_kji  !< dummy to determing local end index in surface type for given (j,i), for for horizonal
    2188                                      !< natural surfaces
    2189     INTEGER(iwp)  ::  num_usm_h      !< current number of horizontal surface element, urban type
    2190     INTEGER(iwp)  ::  num_usm_h_kji  !< dummy to determing local end index in surface type for given (j,i), for for horizonal urban
    2191                                      !< surfaces
     2205    INTEGER(iwp) ::  kk !< auxiliary index z-direction
     2206    INTEGER(iwp) ::  l  !< direction index
     2207
     2208
     2209    INTEGER(iwp), DIMENSION(0:1)  ::  start_index_lsm_h !< dummy to determing local start index in surface type for given (j,i), for horizontal
     2210                                                        !< natural surfaces
     2211    INTEGER(iwp), DIMENSION(0:1)  ::  start_index_usm_h !< dummy to determing local start index in surface type for given (j,i), for horizontal
     2212                                                        !< urban surfaces
     2213    INTEGER(iwp), DIMENSION(0:1)  ::  num_lsm_h         !< current number of horizontal surface element, natural type
     2214    INTEGER(iwp), DIMENSION(0:1)  ::  num_lsm_h_kji     !< dummy to determing local end index in surface type for given (j,i), for for horizonal
     2215                                                        !< natural surfaces
     2216    INTEGER(iwp), DIMENSION(0:1)  ::  num_usm_h         !< current number of horizontal surface element, urban type
     2217    INTEGER(iwp), DIMENSION(0:1)  ::  num_usm_h_kji     !< dummy to determing local end index in surface type for given (j,i), for for horizonal urban
     2218                                                        !< surfaces
    21922219
    21932220    INTEGER(iwp), DIMENSION(0:2) ::  num_def_h          !< current number of horizontal surface element, default type
     
    21972224                                                        !< for horizontal default surfaces
    21982225
    2199     INTEGER(iwp), DIMENSION(0:3) ::  num_def_v      !< current number of vertical surface element, default type
    2200     INTEGER(iwp), DIMENSION(0:3) ::  num_def_v_kji  !< dummy to determing local end index in surface type for given (j,i),
    2201                                                     !< for vertical default surfaces
    2202     INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v      !< current number of vertical surface element, natural type
    2203     INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v_kji  !< dummy to determing local end index in surface type for given (j,i),
    2204                                                     !< for vertical natural surfaces
    2205     INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v      !< current number of vertical surface element, urban type
    2206     INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v_kji  !< dummy to determing local end index in surface type for given (j,i),
    2207                                                     !< for vertical urban surfaces
     2226    INTEGER(iwp), DIMENSION(0:3) ::  num_def_v          !< current number of vertical surface element, default type
     2227    INTEGER(iwp), DIMENSION(0:3) ::  num_def_v_kji      !< dummy to determing local end index in surface type for given (j,i),
     2228                                                        !< for vertical default surfaces
     2229    INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v          !< current number of vertical surface element, natural type
     2230    INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v_kji      !< dummy to determing local end index in surface type for given (j,i),
     2231                                                        !< for vertical natural surfaces
     2232    INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v          !< current number of vertical surface element, urban type
     2233    INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v_kji      !< dummy to determing local end index in surface type for given (j,i),
     2234                                                        !< for vertical urban surfaces
    22082235
    22092236    INTEGER(iwp), DIMENSION(0:3) ::  start_index_def_v  !< dummy to determing local start index in surface type for given (j,i),
     
    22142241                                                        !< for vertical urban surfaces
    22152242
    2216     LOGICAL ::  building             !< flag indicating building grid point
    2217     LOGICAL ::  terrain              !< flag indicating natural terrain grid point
    2218     LOGICAL ::  unresolved_building  !< flag indicating a grid point where actually a building is defined but not resolved by the
    2219                                      !< vertical grid
     2243    LOGICAL ::  building                                !< flag indicating building grid point
     2244    LOGICAL ::  terrain                                 !< flag indicating natural terrain grid point
     2245    LOGICAL ::  unresolved_building                     !< flag indicating a grid point where actually a building is defined but not resolved by the
     2246                                                        !< vertical grid
    22202247!
    22212248!-- Set offset indices, i.e. index difference between surface element and surface-bounded grid point.
     
    22242251    surf_def_h(0:2)%joff = 0
    22252252
    2226     surf_lsm_h%ioff = 0
    2227     surf_lsm_h%joff = 0
    2228 
    2229     surf_usm_h%ioff = 0
    2230     surf_usm_h%joff = 0
     2253    surf_lsm_h(0:1)%ioff = 0
     2254    surf_lsm_h(0:1)%joff = 0
     2255
     2256    surf_usm_h(0:1)%ioff = 0
     2257    surf_usm_h(0:1)%joff = 0
    22312258!
    22322259!-- Upward facing vertical offsets
    22332260    surf_def_h(0)%koff = -1
    2234     surf_lsm_h%koff    = -1
    2235     surf_usm_h%koff    = -1
     2261    surf_lsm_h(0)%koff = -1
     2262    surf_usm_h(0)%koff = -1
    22362263!
    22372264!-- Downward facing vertical offset
    22382265    surf_def_h(1:2)%koff = 1
     2266    surf_lsm_h(1)%koff   = 1
     2267    surf_usm_h(1)%koff   = 1
    22392268!
    22402269!-- Vertical surfaces - no vertical offset
     
    22792308    num_def_v(0:3) = 1
    22802309
    2281     num_lsm_h      = 1
     2310    num_lsm_h(0:1) = 1
    22822311    num_lsm_v(0:3) = 1
    22832312
    2284     num_usm_h      = 1
     2313    num_usm_h(0:1) = 1
    22852314    num_usm_v(0:3) = 1
    22862315
     
    22882317    start_index_def_v(0:3) = 1
    22892318
    2290     start_index_lsm_h      = 1
     2319    start_index_lsm_h(0:1) = 1
    22912320    start_index_lsm_v(0:3) = 1
    22922321
    2293     start_index_usm_h      = 1
     2322    start_index_usm_h(0:1) = 1
    22942323    start_index_usm_v(0:3) = 1
    22952324
     
    23082337             IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
    23092338!
    2310 !--             Upward-facing surface. Distinguish between differet surface types.
    2311 !--             To do, think about method to flag natural and non-natural surfaces.
    2312                 IF ( .NOT. BTEST( wall_flags_total_0(k-1,j,i), 0 ) )  THEN
    2313 !
    2314 !--                Determine flags indicating terrain or building
    2315                    terrain  = BTEST( wall_flags_total_0(k-1,j,i), 5 )  .OR.  topo_no_distinct
    2316                    building = BTEST( wall_flags_total_0(k-1,j,i), 6 )  .OR.  topo_no_distinct
    2317 
    2318 !
    2319 !--                Unresolved_building indicates a surface with equal height as terrain but with a
    2320 !--                non-grid resolved building on top. These surfaces will be flagged as urban
    2321 !--                surfaces.
    2322                    unresolved_building = BTEST( wall_flags_total_0(k-1,j,i), 5 ) .AND.             &
    2323                                          BTEST( wall_flags_total_0(k-1,j,i), 6 )
    2324 !
    2325 !--                Natural surface type
    2326                    IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
    2327                       CALL initialize_horizontal_surfaces( k, j, i, surf_lsm_h, num_lsm_h,         &
    2328                                                            num_lsm_h_kji, .TRUE., .FALSE. )
    2329 !
    2330 !--                Urban surface tpye
    2331                    ELSEIF ( urban_surface  .AND.  building )  THEN
    2332                       CALL initialize_horizontal_surfaces( k, j, i, surf_usm_h, num_usm_h,         &
    2333                                                            num_usm_h_kji, .TRUE., .FALSE. )
    2334 !
    2335 !--                Default surface type
     2339!--             Check if grid point adjoins to any upward- and downward-facing horizontal surface,
     2340!--             e.g. the Earth surface, plane roofs, or ceilings.
     2341                DO kk = k-1, k+1, 2
     2342!
     2343!--                Check for top-fluxes first
     2344                   IF ( kk == nzt+1  .AND.  use_top_fluxes )  THEN
     2345                      CALL initialize_top( k, j, i, surf_def_h(2), num_def_h(2), num_def_h_kji(2) )
    23362346                   ELSE
    2337                       CALL initialize_horizontal_surfaces( k, j, i, surf_def_h(0), num_def_h(0),   &
    2338                                                            num_def_h_kji(0), .TRUE., .FALSE. )
     2347!
     2348!--                   set direction index of the potential surface
     2349                      l = MERGE( 0, 1, kk == k-1 )
     2350!
     2351!--                   Upward- or donward facing surface. Distinguish between differet surface types.
     2352!--                   To do, think about method to flag natural and non-natural surfaces.
     2353                      IF ( .NOT. BTEST( wall_flags_total_0(kk,j,i), 0 ) )  THEN
     2354!
     2355!--                      Determine flags indicating terrain or building
     2356                         terrain  = BTEST( wall_flags_total_0(kk,j,i), 5 )  .OR.  topo_no_distinct
     2357                         building = BTEST( wall_flags_total_0(kk,j,i), 6 )  .OR.  topo_no_distinct
     2358!
     2359!--                      Unresolved_building indicates a surface with equal height as terrain but with a
     2360!--                      non-grid resolved building on top. These surfaces will be flagged as urban
     2361!--                      surfaces.
     2362                         unresolved_building = BTEST( wall_flags_total_0(kk,j,i), 5 ) .AND.       &
     2363                                               BTEST( wall_flags_total_0(kk,j,i), 6 )
     2364!
     2365!--                      Natural surface type
     2366                         IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
     2367                            CALL initialize_horizontal_surfaces( k, j, i, surf_lsm_h(l), num_lsm_h(l), &
     2368                                                                 num_lsm_h_kji(l), .TRUE., .FALSE. )
     2369!
     2370!--                      Urban surface tpye
     2371                         ELSEIF ( urban_surface  .AND.  building )  THEN
     2372                            CALL initialize_horizontal_surfaces( k, j, i, surf_usm_h(l), num_usm_h(l), &
     2373                                                                 num_usm_h_kji(l), .TRUE., .FALSE. )
     2374!
     2375!--                      Default surface type
     2376                         ELSE
     2377                            CALL initialize_horizontal_surfaces( k, j, i, surf_def_h(l), num_def_h(l), &
     2378                                                                 num_def_h_kji(l), .TRUE., .FALSE. )
     2379                         ENDIF
     2380                      ENDIF
    23392381                   ENDIF
    2340                 ENDIF
    2341 !
    2342 !--             Downward-facing surface, first, model top. Please note, for the moment,
    2343 !--             downward-facing surfaces are always of default type
    2344                 IF ( k == nzt  .AND.  use_top_fluxes )  THEN
    2345                    CALL initialize_top( k, j, i, surf_def_h(2), num_def_h(2), num_def_h_kji(2) )
    2346 !
    2347 !--             Check for any other downward-facing surface. So far only for default surface type.
    2348                 ELSEIF ( .NOT. BTEST( wall_flags_total_0(k+1,j,i), 0 ) )  THEN
    2349                    CALL initialize_horizontal_surfaces( k, j, i, surf_def_h(1), num_def_h(1),      &
    2350                                                         num_def_h_kji(1), .FALSE., .TRUE. )
    2351                 ENDIF
     2382                ENDDO
    23522383!
    23532384!--             Check for vertical walls and, if required, initialize it.
     
    24852516          start_index_def_h(2)           = surf_def_h(2)%end_index(j,i) + 1
    24862517!
    2487 !--       Horizontal natural land surfaces
    2488           surf_lsm_h%start_index(j,i)    = start_index_lsm_h
    2489           surf_lsm_h%end_index(j,i)      = surf_lsm_h%start_index(j,i) + num_lsm_h_kji - 1
    2490           start_index_lsm_h              = surf_lsm_h%end_index(j,i) + 1
    2491 !
    2492 !--       Horizontal urban surfaces
    2493           surf_usm_h%start_index(j,i)    = start_index_usm_h
    2494           surf_usm_h%end_index(j,i)      = surf_usm_h%start_index(j,i) + num_usm_h_kji - 1
    2495           start_index_usm_h              = surf_usm_h%end_index(j,i) + 1
     2518!--       Upward- and downward-facing horizontal land and urban surfaces
     2519          DO l = 0, 1
     2520!
     2521!--          Horizontal natural land surfaces
     2522             surf_lsm_h(l)%start_index(j,i) = start_index_lsm_h(l)
     2523             surf_lsm_h(l)%end_index(j,i)   = surf_lsm_h(l)%start_index(j,i) + num_lsm_h_kji(l) - 1
     2524             start_index_lsm_h(l)           = surf_lsm_h(l)%end_index(j,i) + 1
     2525!
     2526!--          Horizontal urban surfaces
     2527             surf_usm_h(l)%start_index(j,i) = start_index_usm_h(l)
     2528             surf_usm_h(l)%end_index(j,i)   = surf_usm_h(l)%start_index(j,i) + num_usm_h_kji(l) - 1
     2529             start_index_usm_h(l)           = surf_usm_h(l)%end_index(j,i) + 1
     2530          ENDDO
    24962531
    24972532!
     
    31383173             ENDDO
    31393174
    3140              IF ( l == 0 )  THEN
    3141                 DO  m = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    3142                    IF ( ALLOCATED( surf_lsm_h%us ) )  surf_h(0)%us(mm(0)) = surf_lsm_h%us(m)
    3143                    IF ( ALLOCATED( surf_lsm_h%ts ) )  surf_h(0)%ts(mm(0)) = surf_lsm_h%ts(m)
    3144                    IF ( ALLOCATED( surf_lsm_h%qs ) )  surf_h(0)%qs(mm(0)) = surf_lsm_h%qs(m)
    3145                    IF ( ALLOCATED( surf_lsm_h%ss ) )  surf_h(0)%ss(mm(0)) = surf_lsm_h%ss(m)
    3146                    IF ( ALLOCATED( surf_lsm_h%qcs ) )  surf_h(0)%qcs(mm(0)) = surf_lsm_h%qcs(m)
    3147                    IF ( ALLOCATED( surf_lsm_h%ncs ) )  surf_h(0)%ncs(mm(0)) = surf_lsm_h%ncs(m)
    3148                    IF ( ALLOCATED( surf_lsm_h%qis ) )  surf_h(0)%qis(mm(0)) = surf_lsm_h%qis(m)
    3149                    IF ( ALLOCATED( surf_lsm_h%nis ) )  surf_h(0)%nis(mm(0)) = surf_lsm_h%nis(m)
    3150                    IF ( ALLOCATED( surf_lsm_h%qrs ) )  surf_h(0)%qrs(mm(0)) = surf_lsm_h%qrs(m)
    3151                    IF ( ALLOCATED( surf_lsm_h%nrs ) )  surf_h(0)%nrs(mm(0)) = surf_lsm_h%nrs(m)
    3152                    IF ( ALLOCATED( surf_lsm_h%ol ) )  surf_h(0)%ol(mm(0)) = surf_lsm_h%ol(m)
    3153                    IF ( ALLOCATED( surf_lsm_h%rib ) )  surf_h(0)%rib(mm(0)) = surf_lsm_h%rib(m)
    3154                    IF ( ALLOCATED( surf_lsm_h%pt_surface ) )                                       &
    3155                       surf_h(l)%pt_surface(mm(l)) = surf_lsm_h%pt_surface(m)
    3156                    IF ( ALLOCATED( surf_def_h(l)%q_surface ) )                                     &
    3157                       surf_h(l)%q_surface(mm(l)) = surf_lsm_h%q_surface(m)
    3158                    IF ( ALLOCATED( surf_def_h(l)%vpt_surface ) )                                   &
    3159                       surf_h(l)%vpt_surface(mm(l)) = surf_lsm_h%vpt_surface(m)
    3160                    IF ( ALLOCATED( surf_lsm_h%usws ) )  surf_h(0)%usws(mm(0)) = surf_lsm_h%usws(m)
    3161                    IF ( ALLOCATED( surf_lsm_h%vsws ) )  surf_h(0)%vsws(mm(0)) = surf_lsm_h%vsws(m)
    3162                    IF ( ALLOCATED( surf_lsm_h%shf ) )  surf_h(0)%shf(mm(0)) = surf_lsm_h%shf(m)
    3163                    IF ( ALLOCATED( surf_lsm_h%qsws ) )  surf_h(0)%qsws(mm(0)) = surf_lsm_h%qsws(m)
    3164                    IF ( ALLOCATED( surf_lsm_h%ssws ) )  surf_h(0)%ssws(mm(0)) = surf_lsm_h%ssws(m)
    3165                    IF ( ALLOCATED( surf_lsm_h%css ) )  THEN
     3175             IF ( l < 2 )  THEN
     3176                DO  m = surf_lsm_h(l)%start_index(j,i), surf_lsm_h(l)%end_index(j,i)
     3177                   IF ( ALLOCATED( surf_lsm_h(l)%us ) )  surf_h(0)%us(mm(0)) = surf_lsm_h(l)%us(m)
     3178                   IF ( ALLOCATED( surf_lsm_h(l)%ts ) )  surf_h(0)%ts(mm(0)) = surf_lsm_h(l)%ts(m)
     3179                   IF ( ALLOCATED( surf_lsm_h(l)%qs ) )  surf_h(0)%qs(mm(0)) = surf_lsm_h(l)%qs(m)
     3180                   IF ( ALLOCATED( surf_lsm_h(l)%ss ) )  surf_h(0)%ss(mm(0)) = surf_lsm_h(l)%ss(m)
     3181                   IF ( ALLOCATED( surf_lsm_h(l)%qcs ) )  surf_h(0)%qcs(mm(0)) = surf_lsm_h(l)%qcs(m)
     3182                   IF ( ALLOCATED( surf_lsm_h(l)%ncs ) )  surf_h(0)%ncs(mm(0)) = surf_lsm_h(l)%ncs(m)
     3183                   IF ( ALLOCATED( surf_lsm_h(l)%qis ) )  surf_h(0)%qis(mm(0)) = surf_lsm_h(l)%qis(m)
     3184                   IF ( ALLOCATED( surf_lsm_h(l)%nis ) )  surf_h(0)%nis(mm(0)) = surf_lsm_h(l)%nis(m)
     3185                   IF ( ALLOCATED( surf_lsm_h(l)%qrs ) )  surf_h(0)%qrs(mm(0)) = surf_lsm_h(l)%qrs(m)
     3186                   IF ( ALLOCATED( surf_lsm_h(l)%nrs ) )  surf_h(0)%nrs(mm(0)) = surf_lsm_h(l)%nrs(m)
     3187                   IF ( ALLOCATED( surf_lsm_h(l)%ol ) )  surf_h(0)%ol(mm(0)) = surf_lsm_h(l)%ol(m)
     3188                   IF ( ALLOCATED( surf_lsm_h(l)%rib ) )  surf_h(0)%rib(mm(0)) = surf_lsm_h(l)%rib(m)
     3189                   IF ( ALLOCATED( surf_lsm_h(l)%pt_surface ) )                                       &
     3190                      surf_h(l)%pt_surface(mm(l)) = surf_lsm_h(l)%pt_surface(m)
     3191                   IF ( ALLOCATED( surf_def_h(l)%q_surface ) )                                        &
     3192                      surf_h(l)%q_surface(mm(l)) = surf_lsm_h(l)%q_surface(m)
     3193                   IF ( ALLOCATED( surf_def_h(l)%vpt_surface ) )                                      &
     3194                      surf_h(l)%vpt_surface(mm(l)) = surf_lsm_h(l)%vpt_surface(m)
     3195                   IF ( ALLOCATED( surf_lsm_h(l)%usws ) )  surf_h(0)%usws(mm(0)) = surf_lsm_h(l)%usws(m)
     3196                   IF ( ALLOCATED( surf_lsm_h(l)%vsws ) )  surf_h(0)%vsws(mm(0)) = surf_lsm_h(l)%vsws(m)
     3197                   IF ( ALLOCATED( surf_lsm_h(l)%shf ) )  surf_h(0)%shf(mm(0)) = surf_lsm_h(l)%shf(m)
     3198                   IF ( ALLOCATED( surf_lsm_h(l)%qsws ) )  surf_h(0)%qsws(mm(0)) = surf_lsm_h(l)%qsws(m)
     3199                   IF ( ALLOCATED( surf_lsm_h(l)%ssws ) )  surf_h(0)%ssws(mm(0)) = surf_lsm_h(l)%ssws(m)
     3200                   IF ( ALLOCATED( surf_lsm_h(l)%css ) )  THEN
    31663201                      DO  lsp = 1, nvar
    3167                          surf_h(0)%css(lsp,mm(0)) = surf_lsm_h%css(lsp,m)
     3202                         surf_h(0)%css(lsp,mm(0)) = surf_lsm_h(l)%css(lsp,m)
    31683203                      ENDDO
    31693204                   ENDIF
    3170                    IF ( ALLOCATED( surf_lsm_h%cssws ) )  THEN
     3205                   IF ( ALLOCATED( surf_lsm_h(l)%cssws ) )  THEN
    31713206                      DO  lsp = 1, nvar
    3172                          surf_h(0)%cssws(lsp,mm(0)) = surf_lsm_h%cssws(lsp,m)
     3207                         surf_h(0)%cssws(lsp,mm(0)) = surf_lsm_h(l)%cssws(lsp,m)
    31733208                      ENDDO
    31743209                   ENDIF
    3175                    IF ( ALLOCATED( surf_lsm_h%qcsws ) )                                            &
    3176                       surf_h(0)%qcsws(mm(0)) = surf_lsm_h%qcsws(m)
    3177                    IF ( ALLOCATED( surf_lsm_h%qisws ) )                                            &
    3178                       surf_h(0)%qisws(mm(0)) = surf_lsm_h%qisws(m)
    3179                    IF ( ALLOCATED( surf_lsm_h%qrsws ) )                                            &
    3180                       surf_h(0)%qrsws(mm(0)) = surf_lsm_h%qrsws(m)
    3181                    IF ( ALLOCATED( surf_lsm_h%ncsws ) )                                            &
    3182                       surf_h(0)%ncsws(mm(0)) = surf_lsm_h%ncsws(m)
    3183                    IF ( ALLOCATED( surf_lsm_h%nisws ) )                                            &
    3184                       surf_h(0)%nisws(mm(0)) = surf_lsm_h%nisws(m)
    3185                    IF ( ALLOCATED( surf_lsm_h%nrsws ) )                                            &
    3186                       surf_h(0)%nrsws(mm(0)) = surf_lsm_h%nrsws(m)
    3187                    IF ( ALLOCATED( surf_lsm_h%sasws ) )                                            &
    3188                      surf_h(0)%sasws(mm(0)) = surf_lsm_h%sasws(m)
    3189 
    3190                    mm(0) = mm(0) + 1
     3210                   IF ( ALLOCATED( surf_lsm_h(l)%qcsws ) )                                            &
     3211                      surf_h(0)%qcsws(mm(0)) = surf_lsm_h(l)%qcsws(m)
     3212                   IF ( ALLOCATED( surf_lsm_h(l)%qisws ) )                                            &
     3213                      surf_h(0)%qisws(mm(0)) = surf_lsm_h(l)%qisws(m)
     3214                   IF ( ALLOCATED( surf_lsm_h(l)%qrsws ) )                                            &
     3215                      surf_h(0)%qrsws(mm(0)) = surf_lsm_h(l)%qrsws(m)
     3216                   IF ( ALLOCATED( surf_lsm_h(l)%ncsws ) )                                            &
     3217                      surf_h(0)%ncsws(mm(0)) = surf_lsm_h(l)%ncsws(m)
     3218                   IF ( ALLOCATED( surf_lsm_h(l)%nisws ) )                                            &
     3219                      surf_h(0)%nisws(mm(0)) = surf_lsm_h(l)%nisws(m)
     3220                   IF ( ALLOCATED( surf_lsm_h(l)%nrsws ) )                                            &
     3221                      surf_h(0)%nrsws(mm(0)) = surf_lsm_h(l)%nrsws(m)
     3222                   IF ( ALLOCATED( surf_lsm_h(l)%sasws ) )                                            &
     3223                     surf_h(0)%sasws(mm(0)) = surf_lsm_h(l)%sasws(m)
     3224
     3225                   mm(l) = mm(l) + 1
    31913226
    31923227                ENDDO
    31933228
    3194                 DO  m = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    3195                    IF ( ALLOCATED( surf_usm_h%us ) )                                               &
    3196                       surf_h(0)%us(mm(0)) = surf_usm_h%us(m)
    3197                    IF ( ALLOCATED( surf_usm_h%ts ) )                                               &
    3198                       surf_h(0)%ts(mm(0)) = surf_usm_h%ts(m)
    3199                    IF ( ALLOCATED( surf_usm_h%qs ) )                                               &
    3200                       surf_h(0)%qs(mm(0)) = surf_usm_h%qs(m)
    3201                    IF ( ALLOCATED( surf_usm_h%ss ) )                                               &
    3202                       surf_h(0)%ss(mm(0)) = surf_usm_h%ss(m)
    3203                    IF ( ALLOCATED( surf_usm_h%qcs ) )                                              &
    3204                       surf_h(0)%qcs(mm(0)) = surf_usm_h%qcs(m)
    3205                    IF ( ALLOCATED( surf_usm_h%ncs ) )                                              &
    3206                       surf_h(0)%ncs(mm(0)) = surf_usm_h%ncs(m)
    3207                    IF ( ALLOCATED( surf_usm_h%qis ) )                                              &
    3208                       surf_h(0)%qis(mm(0)) = surf_usm_h%qis(m)
    3209                    IF ( ALLOCATED( surf_usm_h%nis ) )                                              &
    3210                       surf_h(0)%nis(mm(0)) = surf_usm_h%nis(m)
    3211                    IF ( ALLOCATED( surf_usm_h%qrs ) )                                              &
    3212                       surf_h(0)%qrs(mm(0)) = surf_usm_h%qrs(m)
    3213                    IF ( ALLOCATED( surf_usm_h%nrs ) )                                              &
    3214                       surf_h(0)%nrs(mm(0)) = surf_usm_h%nrs(m)
    3215                    IF ( ALLOCATED( surf_usm_h%ol ) )                                               &
    3216                       surf_h(0)%ol(mm(0)) = surf_usm_h%ol(m)
    3217                    IF ( ALLOCATED( surf_usm_h%rib ) )                                              &
    3218                       surf_h(0)%rib(mm(0)) = surf_usm_h%rib(m)
    3219                    IF ( ALLOCATED( surf_usm_h%pt_surface ) )                                       &
    3220                       surf_h(l)%pt_surface(mm(l)) = surf_usm_h%pt_surface(m)
    3221                     IF ( ALLOCATED( surf_usm_h%q_surface ) )                                       &
    3222                       surf_h(l)%q_surface(mm(l)) = surf_usm_h%q_surface(m)
    3223                    IF ( ALLOCATED( surf_usm_h%vpt_surface ) )                                      &
    3224                       surf_h(l)%vpt_surface(mm(l)) = surf_usm_h%vpt_surface(m)
    3225                    IF ( ALLOCATED( surf_usm_h%usws ) )                                             &
    3226                       surf_h(0)%usws(mm(0)) = surf_usm_h%usws(m)
    3227                    IF ( ALLOCATED( surf_usm_h%vsws ) )                                             &
    3228                       surf_h(0)%vsws(mm(0)) = surf_usm_h%vsws(m)
    3229                    IF ( ALLOCATED( surf_usm_h%shf ) )                                              &
    3230                       surf_h(0)%shf(mm(0)) = surf_usm_h%shf(m)
    3231                    IF ( ALLOCATED( surf_usm_h%qsws ) )                                             &
    3232                       surf_h(0)%qsws(mm(0)) = surf_usm_h%qsws(m)
    3233                    IF ( ALLOCATED( surf_usm_h%ssws ) )                                             &
    3234                       surf_h(0)%ssws(mm(0)) = surf_usm_h%ssws(m)
    3235                    IF ( ALLOCATED( surf_usm_h%css ) )  THEN
     3229                DO  m = surf_usm_h(l)%start_index(j,i), surf_usm_h(l)%end_index(j,i)
     3230                   IF ( ALLOCATED( surf_usm_h(l)%us ) )                                               &
     3231                      surf_h(0)%us(mm(0)) = surf_usm_h(l)%us(m)
     3232                   IF ( ALLOCATED( surf_usm_h(l)%ts ) )                                               &
     3233                      surf_h(0)%ts(mm(0)) = surf_usm_h(l)%ts(m)
     3234                   IF ( ALLOCATED( surf_usm_h(l)%qs ) )                                               &
     3235                      surf_h(0)%qs(mm(0)) = surf_usm_h(l)%qs(m)
     3236                   IF ( ALLOCATED( surf_usm_h(l)%ss ) )                                               &
     3237                      surf_h(0)%ss(mm(0)) = surf_usm_h(l)%ss(m)
     3238                   IF ( ALLOCATED( surf_usm_h(l)%qcs ) )                                              &
     3239                      surf_h(0)%qcs(mm(0)) = surf_usm_h(l)%qcs(m)
     3240                   IF ( ALLOCATED( surf_usm_h(l)%ncs ) )                                              &
     3241                      surf_h(0)%ncs(mm(0)) = surf_usm_h(l)%ncs(m)
     3242                   IF ( ALLOCATED( surf_usm_h(l)%qis ) )                                              &
     3243                      surf_h(0)%qis(mm(0)) = surf_usm_h(l)%qis(m)
     3244                   IF ( ALLOCATED( surf_usm_h(l)%nis ) )                                              &
     3245                      surf_h(0)%nis(mm(0)) = surf_usm_h(l)%nis(m)
     3246                   IF ( ALLOCATED( surf_usm_h(l)%qrs ) )                                              &
     3247                      surf_h(0)%qrs(mm(0)) = surf_usm_h(l)%qrs(m)
     3248                   IF ( ALLOCATED( surf_usm_h(l)%nrs ) )                                              &
     3249                      surf_h(0)%nrs(mm(0)) = surf_usm_h(l)%nrs(m)
     3250                   IF ( ALLOCATED( surf_usm_h(l)%ol ) )                                               &
     3251                      surf_h(0)%ol(mm(0)) = surf_usm_h(l)%ol(m)
     3252                   IF ( ALLOCATED( surf_usm_h(l)%rib ) )                                              &
     3253                      surf_h(0)%rib(mm(0)) = surf_usm_h(l)%rib(m)
     3254                   IF ( ALLOCATED( surf_usm_h(l)%pt_surface ) )                                       &
     3255                      surf_h(l)%pt_surface(mm(l)) = surf_usm_h(l)%pt_surface(m)
     3256                    IF ( ALLOCATED( surf_usm_h(l)%q_surface ) )                                       &
     3257                      surf_h(l)%q_surface(mm(l)) = surf_usm_h(l)%q_surface(m)
     3258                   IF ( ALLOCATED( surf_usm_h(l)%vpt_surface ) )                                      &
     3259                      surf_h(l)%vpt_surface(mm(l)) = surf_usm_h(l)%vpt_surface(m)
     3260                   IF ( ALLOCATED( surf_usm_h(l)%usws ) )                                             &
     3261                      surf_h(0)%usws(mm(0)) = surf_usm_h(l)%usws(m)
     3262                   IF ( ALLOCATED( surf_usm_h(l)%vsws ) )                                             &
     3263                      surf_h(0)%vsws(mm(0)) = surf_usm_h(l)%vsws(m)
     3264                   IF ( ALLOCATED( surf_usm_h(l)%shf ) )                                              &
     3265                      surf_h(0)%shf(mm(0)) = surf_usm_h(l)%shf(m)
     3266                   IF ( ALLOCATED( surf_usm_h(l)%qsws ) )                                             &
     3267                      surf_h(0)%qsws(mm(0)) = surf_usm_h(l)%qsws(m)
     3268                   IF ( ALLOCATED( surf_usm_h(l)%ssws ) )                                             &
     3269                      surf_h(0)%ssws(mm(0)) = surf_usm_h(l)%ssws(m)
     3270                   IF ( ALLOCATED( surf_usm_h(l)%css ) )  THEN
    32363271                      DO lsp = 1, nvar
    3237                          surf_h(0)%css(lsp,mm(0)) = surf_usm_h%css(lsp,m)
     3272                         surf_h(0)%css(lsp,mm(0)) = surf_usm_h(l)%css(lsp,m)
    32383273                      ENDDO
    32393274                   ENDIF
    3240                    IF ( ALLOCATED( surf_usm_h%cssws ) )  THEN
     3275                   IF ( ALLOCATED( surf_usm_h(l)%cssws ) )  THEN
    32413276                      DO lsp = 1, nvar
    3242                          surf_h(0)%cssws(lsp,mm(0)) = surf_usm_h%cssws(lsp,m)
     3277                         surf_h(0)%cssws(lsp,mm(0)) = surf_usm_h(l)%cssws(lsp,m)
    32433278                      ENDDO
    32443279                   ENDIF
    3245                    IF ( ALLOCATED( surf_usm_h%qcsws ) )                                            &
    3246                       surf_h(0)%qcsws(mm(0)) = surf_usm_h%qcsws(m)
    3247                    IF ( ALLOCATED( surf_usm_h%qisws ) )                                            &
    3248                       surf_h(0)%qisws(mm(0)) = surf_usm_h%qisws(m)
    3249                    IF ( ALLOCATED( surf_usm_h%qrsws ) )                                            &
    3250                       surf_h(0)%qrsws(mm(0)) = surf_usm_h%qrsws(m)
    3251                    IF ( ALLOCATED( surf_usm_h%ncsws ) )                                            &
    3252                       surf_h(0)%ncsws(mm(0))   = surf_usm_h%ncsws(m)
    3253                    IF ( ALLOCATED( surf_usm_h%nrsws ) )                                            &
    3254                       surf_h(0)%nrsws(mm(0)) = surf_usm_h%nrsws(m)
    3255                    IF ( ALLOCATED( surf_usm_h%nisws ) )                                            &
    3256                       surf_h(0)%nisws(mm(0)) = surf_usm_h%nisws(m)
    3257                    IF ( ALLOCATED( surf_usm_h%sasws ) )                                            &
    3258                      surf_h(0)%sasws(mm(0)) = surf_usm_h%sasws(m)
    3259 
    3260                    mm(0) = mm(0) + 1
     3280                   IF ( ALLOCATED( surf_usm_h(l)%qcsws ) )                                            &
     3281                      surf_h(0)%qcsws(mm(0)) = surf_usm_h(l)%qcsws(m)
     3282                   IF ( ALLOCATED( surf_usm_h(l)%qisws ) )                                            &
     3283                      surf_h(0)%qisws(mm(0)) = surf_usm_h(l)%qisws(m)
     3284                   IF ( ALLOCATED( surf_usm_h(l)%qrsws ) )                                            &
     3285                      surf_h(0)%qrsws(mm(0)) = surf_usm_h(l)%qrsws(m)
     3286                   IF ( ALLOCATED( surf_usm_h(l)%ncsws ) )                                            &
     3287                      surf_h(0)%ncsws(mm(0))   = surf_usm_h(l)%ncsws(m)
     3288                   IF ( ALLOCATED( surf_usm_h(l)%nrsws ) )                                            &
     3289                      surf_h(0)%nrsws(mm(0)) = surf_usm_h(l)%nrsws(m)
     3290                   IF ( ALLOCATED( surf_usm_h(l)%nisws ) )                                            &
     3291                      surf_h(0)%nisws(mm(0)) = surf_usm_h(l)%nisws(m)
     3292                   IF ( ALLOCATED( surf_usm_h(l)%sasws ) )                                            &
     3293                     surf_h(0)%sasws(mm(0)) = surf_usm_h(l)%sasws(m)
     3294
     3295                   mm(l) = mm(l) + 1
    32613296
    32623297                ENDDO
     
    32803315                surf_h(l)%end_index(j,i) = surf_h(l)%end_index(j,i) + 1
    32813316             ENDDO
    3282              IF ( l == 0 )  THEN
    3283                 DO  m = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
     3317             IF ( l < 2 )  THEN
     3318                DO  m = surf_lsm_h(l)%start_index(j,i), surf_lsm_h(l)%end_index(j,i)
    32843319                   surf_h(l)%end_index(j,i) = surf_h(l)%end_index(j,i) + 1
    32853320                ENDDO
    3286                 DO  m = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
     3321                DO  m = surf_usm_h(l)%start_index(j,i), surf_usm_h(l)%end_index(j,i)
    32873322                   surf_h(l)%end_index(j,i) = surf_h(l)%end_index(j,i) + 1
    32883323                ENDDO
     
    49775012!--          Determine type of surface element, i.e. default, natural, urban, at current grid point.
    49785013             surf_match_def  = surf_def_h(l)%end_index(jc,ic) >= surf_def_h(l)%start_index(jc,ic)
    4979              surf_match_lsm  = ( surf_lsm_h%end_index(jc,ic)  >= surf_lsm_h%start_index(jc,ic) )   &
    4980                                 .AND.  l == 0
    4981              surf_match_usm  = ( surf_usm_h%end_index(jc,ic)  >= surf_usm_h%start_index(jc,ic) )   &
    4982                                  .AND.  l == 0
     5014             IF ( l < 2 ) THEN
     5015                surf_match_lsm  = surf_lsm_h(l)%end_index(jc,ic) >= surf_lsm_h(l)%start_index(jc,ic)
     5016                surf_match_usm  = surf_usm_h(l)%end_index(jc,ic) >= surf_usm_h(l)%start_index(jc,ic)
     5017             ELSE
     5018                surf_match_lsm  = .FALSE.
     5019                surf_match_usm  = .FALSE.
     5020             ENDIF
    49835021!
    49845022!--          Write restart data onto default-type surfaces if required.
     
    50025040!--          surfaces at (j,i). An example would be bridges.
    50035041             IF ( surf_match_lsm )  THEN
    5004                 mm = surf_lsm_h%start_index(jc,ic)
     5042                mm = surf_lsm_h(l)%start_index(jc,ic)
    50055043                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
    5006                    IF ( surf_lsm_h%end_index(jc,ic) >= mm )                                        &
    5007                       CALL restore_surface_elements( surf_lsm_h, mm, surf_h(l), m )
     5044                   IF ( surf_lsm_h(l)%end_index(jc,ic) >= mm )                                        &
     5045                      CALL restore_surface_elements( surf_lsm_h(l), mm, surf_h(l), m )
    50085046                   mm = mm + 1
    50095047                ENDDO
     
    50125050!--          Same for urban-type surfaces
    50135051             IF ( surf_match_usm )  THEN
    5014                 mm = surf_usm_h%start_index(jc,ic)
     5052                mm = surf_usm_h(l)%start_index(jc,ic)
    50155053                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
    5016                    IF ( surf_usm_h%end_index(jc,ic) >= mm )                                        &
    5017                       CALL restore_surface_elements( surf_usm_h, mm, surf_h(l), m )
     5054                   IF ( surf_usm_h(l)%end_index(jc,ic) >= mm )                                        &
     5055                      CALL restore_surface_elements( surf_usm_h(l), mm, surf_h(l), m )
    50185056                   mm = mm + 1
    50195057                ENDDO
     
    56065644    DO  i = nxl, nxr
    56075645       DO  j = nys, nyn
    5608           surf_match_lsm  = surf_lsm_h%end_index(j,i) >= surf_lsm_h%start_index(j,i)
    5609           surf_match_usm  = surf_usm_h%end_index(j,i) >= surf_usm_h%start_index(j,i)
     5646          surf_match_lsm  = surf_lsm_h(l)%end_index(j,i) >= surf_lsm_h(l)%start_index(j,i)
     5647          surf_match_usm  = surf_usm_h(l)%end_index(j,i) >= surf_usm_h(l)%start_index(j,i)
    56105648
    56115649          IF ( surf_match_lsm )  THEN
    5612              mm = surf_lsm_h%start_index(j,i)
     5650             mm = surf_lsm_h(l)%start_index(j,i)
    56135651             DO  m = surf_h(0)%start_index(j,i), surf_h(0)%end_index(j,i)
    5614                 IF ( surf_lsm_h%end_index(j,i) >= mm )                                             &
    5615                    CALL restore_surface_elements( surf_lsm_h, mm, surf_h(0), m )
     5652                IF ( surf_lsm_h(l)%end_index(j,i) >= mm )                                             &
     5653                   CALL restore_surface_elements( surf_lsm_h(l), mm, surf_h(0), m )
    56165654                mm = mm + 1
    56175655             ENDDO
     
    56195657
    56205658          IF ( surf_match_usm )  THEN
    5621              mm = surf_usm_h%start_index(j,i)
     5659             mm = surf_usm_h(l)%start_index(j,i)
    56225660             DO  m = surf_h(0)%start_index(j,i), surf_h(0)%end_index(j,i)
    5623                 IF ( surf_usm_h%end_index(j,i) >= mm )                                             &
    5624                    CALL restore_surface_elements( surf_usm_h, mm, surf_h(0), m )
     5661                IF ( surf_usm_h(l)%end_index(j,i) >= mm )                                             &
     5662                   CALL restore_surface_elements( surf_usm_h(l), mm, surf_h(0), m )
    56255663                mm = mm + 1
    56265664             ENDDO
     
    58025840!
    58035841!-- Horizontal surfaces
    5804     ns_h_on_file(0) = surf_def_h(0)%ns + surf_lsm_h%ns + surf_usm_h%ns
    5805     ns_h_on_file(1) = surf_def_h(1)%ns
     5842    ns_h_on_file(0) = surf_def_h(0)%ns + surf_lsm_h(0)%ns + surf_usm_h(0)%ns
     5843    ns_h_on_file(1) = surf_def_h(1)%ns + surf_lsm_h(1)%ns + surf_usm_h(1)%ns
    58065844    ns_h_on_file(2) = surf_def_h(2)%ns
    58075845!
Note: See TracChangeset for help on using the changeset viewer.