source: palm/trunk/SOURCE/surface_mod.f90 @ 2300

Last change on this file since 2300 was 2292, checked in by schwenkel, 7 years ago

implementation of new bulk microphysics scheme

  • Property svn:keywords set to Id
File size: 159.3 KB
Line 
1!> @file surface_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2017 Leibniz Universitaet Hannover
18!
19!------------------------------------------------------------------------------!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: surface_mod.f90 2292 2017-06-20 09:51:42Z raasch $
27! Implementation of new microphysic scheme: cloud_scheme = 'morrison'
28! includes two more prognostic equations for cloud drop concentration (nc) 
29! and cloud water content (qc).
30!
31! 2270 2017-06-09 12:18:47Z maronga
32! Parameters removed/added due to changes in the LSM
33!
34! 2269 2017-06-09 11:57:32Z suehring
35! Formatting and description adjustments
36!
37! 2256 2017-06-07 13:58:08Z suehring
38! Enable heating at downward-facing surfaces
39!
40! 2233 2017-05-30 18:08:54Z suehring
41! Initial revision
42!
43!
44! Description:
45! ------------
46!> Surface module defines derived data structures to treat surface-
47!> bounded grid cells. Three different types of surfaces are defined:
48!> default surfaces, natural surfaces, and urban surfaces. The module
49!> encompasses the allocation and initialization of surface arrays, and handles
50!> reading and writing restart data.
51!> In addition, a further derived data structure is defined, in order to set
52!> boundary conditions at surfaces. 
53!------------------------------------------------------------------------------!
54 MODULE surface_mod
55
56    USE arrays_3d,                                                             &
57        ONLY:  zu, zw, heatflux_input_conversion, waterflux_input_conversion,  &
58               momentumflux_input_conversion
59
60    USE control_parameters               
61
62    USE indices,                                                               &
63        ONLY:  nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt, wall_flags_0
64
65    USE grid_variables,                                                        &
66        ONLY:  dx, dy
67
68    USE kinds
69
70    USE model_1d,                                                              &
71        ONLY:  rif1d, us1d, usws1d, vsws1d
72       
73
74    IMPLICIT NONE
75
76!
77!-- Data type used to identify grid-points where horizontal boundary conditions
78!-- are applied
79    TYPE bc_type
80
81       INTEGER(iwp) :: ns                                  !< number of surface elements on the PE
82
83       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i       !< x-index linking to the PALM 3D-grid 
84       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j       !< y-index linking to the PALM 3D-grid   
85       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k       !< z-index linking to the PALM 3D-grid   
86
87       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE :: start_index !< start index within surface data type for given (j,i)
88       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE :: end_index   !< end index within surface data type for given (j,i) 
89
90    END TYPE bc_type
91!
92!-- Data type used to identify and treat surface-bounded grid points 
93    TYPE surf_type
94
95       INTEGER(iwp) :: ns                                  !< number of surface elements on the PE
96       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i       !< x-index linking to the PALM 3D-grid 
97       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j       !< y-index linking to the PALM 3D-grid   
98       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k       !< z-index linking to the PALM 3D-grid       
99
100       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  facing  !< Bit indicating surface orientation
101     
102       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE :: start_index !< Start index within surface data type for given (j,i)
103       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE :: end_index   !< End index within surface data type for given (j,i) 
104
105       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z_mo      !< surface-layer height
106       REAL(wp), DIMENSION(:), ALLOCATABLE ::  uvw_abs   !< absolute surface-parallel velocity
107       REAL(wp), DIMENSION(:), ALLOCATABLE ::  us        !< friction velocity
108       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts        !< scaling parameter temerature
109       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qs        !< scaling parameter humidity
110       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ss        !< scaling parameter passive scalar
111       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qcs       !< scaling parameter qc
112       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ncs       !< scaling parameter nc
113       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qrs       !< scaling parameter qr
114       REAL(wp), DIMENSION(:), ALLOCATABLE ::  nrs       !< scaling parameter nr
115
116       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ol        !< Obukhov length
117       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rib       !< Richardson bulk number
118
119       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0        !< roughness length for momentum
120       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0h       !< roughness length for heat
121       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0q       !< roughness length for humidity
122
123       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt1       !< Specific humidity at first grid level (required for cloud_physics = .T.)
124       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qv1       !< Potential temperature at first grid level (required for cloud_physics = .T.)
125!
126!--    Define arrays for surface fluxes
127       REAL(wp), DIMENSION(:), ALLOCATABLE ::  usws      !< vertical momentum flux for u-component at horizontal surfaces
128       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vsws      !< vertical momentum flux for v-component at horizontal surfaces
129
130       REAL(wp), DIMENSION(:), ALLOCATABLE ::  shf       !< surface flux sensible heat
131       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws      !< surface flux latent heat
132       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ssws      !< surface flux passive scalar
133       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qcsws     !< surface flux qc
134       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ncsws     !< surface flux nc
135       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qrsws     !< surface flux qr
136       REAL(wp), DIMENSION(:), ALLOCATABLE ::  nrsws     !< surface flux nr
137       REAL(wp), DIMENSION(:), ALLOCATABLE ::  sasws     !< surface flux salinity
138!
139!--    Required for horizontal walls in production_e
140       REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_0       !< virtual velocity component (see production_e_init for further explanation)
141       REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_0       !< virtual velocity component (see production_e_init for further explanation)
142
143       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  mom_flux_uv  !< momentum flux usvs and vsus at vertical surfaces (used in diffusion_u and diffusion_v)
144       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  mom_flux_w   !< momentum flux wsus and wsvs at vertical surfaces (used in diffusion_w)
145       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  mom_flux_tke !< momentum flux usvs, vsus, wsus, wsvs at vertical surfaces at grid center (used in production_e)
146!
147!--    Variables required for LSM as well as for USM
148       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  pt_surface        !< skin-surface temperature
149       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  rad_net_l         !< net radiation
150       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_h          !< heat conductivity of soil (W/m/K)
151       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  lambda_h_def      !< default heat conductivity of soil (W/m/K)   
152       
153       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  building_surface    !< flag parameter indicating that the surface element is covered by buildings (no LSM actions, not implemented yet)
154       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  pavement_surface    !< flag parameter for pavements
155       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  water_surface       !< flag parameter for water surfaces
156       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  vegetation_surface     !< flag parameter for natural land surfaces
157
158       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_liq               !< liquid water coverage (of vegetated area)
159       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_veg               !< vegetation coverage
160       REAL(wp), DIMENSION(:), ALLOCATABLE ::  f_sw_in             !< fraction of absorbed shortwave radiation by the surface layer (not implemented yet)
161       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ghf              !< ground heat flux
162       REAL(wp), DIMENSION(:), ALLOCATABLE ::  g_d                 !< coefficient for dependence of r_canopy on water vapour pressure deficit
163       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lai                 !< leaf area index
164       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surface_u    !< coupling between surface and soil (depends on vegetation type) (W/m2/K)
165       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surface_s    !< coupling between surface and soil (depends on vegetation type) (W/m2/K)
166       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_liq         !< surface flux of latent heat (liquid water portion)
167       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_soil        !< surface flux of latent heat (soil portion)
168       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_veg         !< surface flux of latent heat (vegetation portion)
169       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_a                 !< aerodynamic resistance
170       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_canopy            !< canopy resistance
171       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_soil              !< soil resistance
172       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_soil_min          !< minimum soil resistance
173       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_s                 !< total surface resistance (combination of r_soil and r_canopy)
174       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_canopy_min        !< minimum canopy (stomatal) resistance
175
176       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  alpha_vg          !< coef. of Van Genuchten
177       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_w          !< hydraulic diffusivity of soil (?)
178       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gamma_w           !< hydraulic conductivity of soil (W/m/K)
179       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gamma_w_sat       !< hydraulic conductivity at saturation
180       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  l_vg              !< coef. of Van Genuchten
181       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_fc              !< soil moisture at field capacity (m3/m3)
182       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_res             !< residual soil moisture
183       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_sat             !< saturation soil moisture (m3/m3)
184       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_wilt            !< soil moisture at permanent wilting point (m3/m3)
185       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_vg              !< coef. Van Genuchten 
186       REAL(wp), DIMENSION(:),   ALLOCATABLE ::  rho_c_def         !< default volumetric heat capacity of the (soil) layer (J/m3/K)
187       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_total       !< volumetric heat capacity of the actual soil matrix (J/m3/K)
188       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  root_fr           !< root fraction within the soil layers
189!
190!--    Urban surface variables
191       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  surface_types   !< array of types of wall parameters
192
193       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  isroof_surf         !< flag indication roof surfaces
194
195       REAL(wp), DIMENSION(:), ALLOCATABLE ::  albedo_surf         !< albedo of the surface
196       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_surface           !< heat capacity of the wall surface skin (J/m2/K)
197       REAL(wp), DIMENSION(:), ALLOCATABLE ::  emiss_surf          !< emissivity of the wall surface
198       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surf         !< heat conductivity between air and surface (W/m2/K)
199       REAL(wp), DIMENSION(:), ALLOCATABLE ::  roughness_wall      !< roughness relative to concrete
200       REAL(wp), DIMENSION(:), ALLOCATABLE ::  thickness_wall      !< thickness of the wall, roof and soil layers
201
202       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutsl           !< reflected shortwave radiation for local surface in i-th reflection
203       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutll           !< reflected + emitted longwave radiation for local surface in i-th reflection
204       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfhf              !< total radiation flux incoming to minus outgoing from local surface
205
206       REAL(wp), DIMENSION(:), ALLOCATABLE ::  tt_surface_m        !< surface temperature tendency (K)
207       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wshf                !< kinematic wall heat flux of sensible heat (actually no longer needed)
208       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wshf_eb             !< wall heat flux of sensible heat in wall normal direction
209
210
211       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb             !< wall ground heat flux
212
213       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_in_sw           !< incoming shortwave radiation
214       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_out_sw          !< emitted shortwave radiation
215       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_in_lw           !< incoming longwave radiation
216       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_out_lw          !< emitted longwave radiation
217
218       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinsw            !< shortwave radiation falling to local surface including radiation from reflections
219       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutsw           !< total shortwave radiation outgoing from nonvirtual surfaces surfaces after all reflection
220       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlw            !< longwave radiation falling to local surface including radiation from reflections
221       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutlw           !< total longwave radiation outgoing from nonvirtual surfaces surfaces after all reflection
222
223
224       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_wall        !< volumetric heat capacity of the material ( J m-3 K-1 ) (= 2.19E6)
225       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_wall           !< wall grid spacing (center-center)
226       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_wall          !< 1/dz_wall
227       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_wall_stag      !< wall grid spacing (edge-edge)
228       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_wall_stag     !< 1/dz_wall_stag
229       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tt_wall_m         !< t_wall prognostic array
230       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw                !< wall layer depths (m)
231
232
233!-- arrays for time averages
234       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_net_av       !< average of rad_net_l
235       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinsw_av      !< average of sw radiation falling to local surface including radiation from reflections
236       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlw_av      !< average of lw radiation falling to local surface including radiation from reflections
237       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinswdir_av   !< average of direct sw radiation falling to local surface
238       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinswdif_av   !< average of diffuse sw radiation from sky and model boundary falling to local surface
239       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlwdif_av   !< average of diffuse lw radiation from sky and model boundary falling to local surface
240       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinswref_av   !< average of sw radiation falling to surface from reflections
241       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlwref_av   !< average of lw radiation falling to surface from reflections
242       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutsw_av     !< average of total sw radiation outgoing from nonvirtual surfaces surfaces after all reflection
243       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutlw_av     !< average of total lw radiation outgoing from nonvirtual surfaces surfaces after all reflection
244       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfins_av       !< average of array of residua of sw radiation absorbed in surface after last reflection
245       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinl_av       !< average of array of residua of lw radiation absorbed in surface after last reflection
246       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfhf_av        !< average of total radiation flux incoming to minus outgoing from local surface 
247       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb_av       !< average of wghf_eb
248       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wshf_eb_av       !< average of wshf_eb
249       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_surf_av        !< average of wall surface temperature (K)
250
251       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  t_wall_av      !< Average of t_wall
252
253    END TYPE surf_type
254
255    TYPE (bc_type), DIMENSION(0:1)           ::  bc_h        !< boundary condition data type, horizontal upward- and downward facing surfaces
256
257    TYPE (surf_type), DIMENSION(0:2), TARGET ::  surf_def_h  !< horizontal default surfaces (Up, Down, and Top)
258    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_def_v  !< vertical default surfaces (North, South, West, East)
259    TYPE (surf_type)                , TARGET ::  surf_lsm_h  !< horizontal natural land surfaces, so far only upward-facing
260    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_lsm_v  !< vertical land surfaces (North, South, West, East)
261    TYPE (surf_type)                , TARGET ::  surf_usm_h  !< horizontal urban surfaces, so far only upward-facing
262    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_usm_v  !< vertical urban surfaces (North, South, West, East)
263
264    INTEGER(iwp) ::  ns_h_on_file(0:2)                       !< total number of horizontal surfaces with the same facing, required for writing restart data
265    INTEGER(iwp) ::  ns_v_on_file(0:3)                       !< total number of vertical surfaces with the same facing, required for writing restart data
266
267
268    SAVE
269
270    PRIVATE
271!
272!-- Public variables
273    PUBLIC bc_h, ns_h_on_file, ns_v_on_file, surf_def_h, surf_def_v,           &
274           surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v, surf_type
275!
276!-- Public subroutines
277    PUBLIC init_bc, init_surfaces, init_surface_arrays,                        &
278           surface_read_restart_data, surface_write_restart_data,              &
279           surface_last_actions
280
281    INTERFACE init_bc
282       MODULE PROCEDURE init_bc
283    END INTERFACE init_bc
284
285    INTERFACE init_surfaces
286       MODULE PROCEDURE init_surfaces
287    END INTERFACE init_surfaces
288
289    INTERFACE init_surface_arrays
290       MODULE PROCEDURE init_surface_arrays
291    END INTERFACE init_surface_arrays
292
293    INTERFACE surface_read_restart_data
294       MODULE PROCEDURE surface_read_restart_data
295    END INTERFACE surface_read_restart_data
296
297    INTERFACE surface_write_restart_data
298       MODULE PROCEDURE surface_write_restart_data
299    END INTERFACE surface_write_restart_data
300
301    INTERFACE surface_last_actions
302       MODULE PROCEDURE surface_last_actions
303    END INTERFACE surface_last_actions
304
305
306 CONTAINS
307
308!------------------------------------------------------------------------------!
309! Description:
310! ------------
311!> Initialize data type for setting boundary conditions at horizontal surfaces.
312!------------------------------------------------------------------------------!
313    SUBROUTINE init_bc
314
315       IMPLICIT NONE
316
317       INTEGER(iwp) ::  i         !<
318       INTEGER(iwp) ::  j         !<
319       INTEGER(iwp) ::  k         !<
320
321       INTEGER(iwp), DIMENSION(0:1) ::  num_h         !<
322       INTEGER(iwp), DIMENSION(0:1) ::  num_h_kji     !<
323       INTEGER(iwp), DIMENSION(0:1) ::  start_index_h !<
324
325!
326!--    First of all, count the number of upward- and downward-facing surfaces
327       num_h = 0
328       DO  i = nxlg, nxrg
329          DO  j = nysg, nyng
330             DO  k = nzb+1, nzt
331!
332!--             Check if current gridpoint belongs to the atmosphere
333                IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
334!
335!--                Upward-facing
336                   IF ( .NOT. BTEST( wall_flags_0(k-1,j,i), 0 ) )              &
337                      num_h(0) = num_h(0) + 1
338!
339!--                Downward-facing
340                   IF ( .NOT. BTEST( wall_flags_0(k+1,j,i), 0 ) )              &
341                      num_h(1) = num_h(1) + 1
342                ENDIF
343             ENDDO
344          ENDDO
345       ENDDO
346!
347!--    Save the number of surface elements
348       bc_h(0)%ns = num_h(0)
349       bc_h(1)%ns = num_h(1)
350!
351!--    ALLOCATE data type variables
352!--    Upward facing
353       ALLOCATE( bc_h(0)%i(1:bc_h(0)%ns) )
354       ALLOCATE( bc_h(0)%j(1:bc_h(0)%ns) )
355       ALLOCATE( bc_h(0)%k(1:bc_h(0)%ns) )
356       ALLOCATE( bc_h(0)%start_index(nysg:nyng,nxlg:nxrg) )
357       ALLOCATE( bc_h(0)%end_index(nysg:nyng,nxlg:nxrg)   )
358       bc_h(0)%start_index = 1
359       bc_h(0)%end_index   = 0
360!
361!--    Downward facing
362       ALLOCATE( bc_h(1)%i(1:bc_h(1)%ns) )
363       ALLOCATE( bc_h(1)%j(1:bc_h(1)%ns) )
364       ALLOCATE( bc_h(1)%k(1:bc_h(1)%ns) )
365       ALLOCATE( bc_h(1)%start_index(nysg:nyng,nxlg:nxrg) )
366       ALLOCATE( bc_h(1)%end_index(nysg:nyng,nxlg:nxrg)   )
367       bc_h(1)%start_index = 1
368       bc_h(1)%end_index   = 0
369!
370!--    Store the respective indices on data type
371       num_h(0:1)         = 1
372       start_index_h(0:1) = 1
373       DO  i = nxlg, nxrg
374          DO  j = nysg, nyng
375
376             num_h_kji(0:1) = 0
377             DO  k = nzb+1, nzt
378!
379!--             Check if current gridpoint belongs to the atmosphere
380                IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
381!
382!--                Upward-facing
383                   IF ( .NOT. BTEST( wall_flags_0(k-1,j,i), 0 ) )  THEN
384                      bc_h(0)%i(num_h(0)) = i
385                      bc_h(0)%j(num_h(0)) = j
386                      bc_h(0)%k(num_h(0)) = k
387                      num_h_kji(0)        = num_h_kji(0) + 1
388                      num_h(0)            = num_h(0) + 1
389                   ENDIF
390!
391!--                Downward-facing
392                   IF ( .NOT. BTEST( wall_flags_0(k+1,j,i), 0 ) )  THEN
393                      bc_h(1)%i(num_h(1)) = i
394                      bc_h(1)%j(num_h(1)) = j
395                      bc_h(1)%k(num_h(1)) = k
396                      num_h_kji(1)        = num_h_kji(1) + 1
397                      num_h(1)            = num_h(1) + 1
398                   ENDIF
399                ENDIF
400             ENDDO
401             bc_h(0)%start_index(j,i) = start_index_h(0)
402             bc_h(0)%end_index(j,i)   = bc_h(0)%start_index(j,i) + num_h_kji(0) - 1
403             start_index_h(0)         = bc_h(0)%end_index(j,i) + 1
404
405             bc_h(1)%start_index(j,i) = start_index_h(1)
406             bc_h(1)%end_index(j,i)   = bc_h(1)%start_index(j,i) + num_h_kji(1) - 1
407             start_index_h(1)         = bc_h(1)%end_index(j,i) + 1
408          ENDDO
409       ENDDO
410
411
412    END SUBROUTINE init_bc
413
414
415!------------------------------------------------------------------------------!
416! Description:
417! ------------
418!> Initialize horizontal and vertical surfaces. Counts the number of default-,
419!> natural and urban surfaces and allocates memory, respectively.
420!------------------------------------------------------------------------------!
421    SUBROUTINE init_surface_arrays
422
423       IMPLICIT NONE
424
425       INTEGER(iwp)                 ::  i         !< running index x-direction
426       INTEGER(iwp)                 ::  j         !< running index y-direction
427       INTEGER(iwp)                 ::  k         !< running index z-direction
428       INTEGER(iwp)                 ::  l         !< index variable for surface facing
429       INTEGER(iwp)                 ::  num_lsm_h !< number of horizontally-aligned natural surfaces
430       INTEGER(iwp)                 ::  num_usm_h !< number of horizontally-aligned urban surfaces
431
432       INTEGER(iwp), DIMENSION(0:2) ::  num_def_h !< number of horizontally-aligned default surfaces
433       INTEGER(iwp), DIMENSION(0:3) ::  num_def_v !< number of vertically-aligned default surfaces
434       INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v !< number of vertically-aligned natural surfaces
435       INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v !< number of vertically-aligned urban surfaces
436
437
438       num_def_h = 0
439       num_def_v = 0
440       num_lsm_h = 0
441       num_lsm_v = 0
442       num_usm_h = 0
443       num_usm_v = 0
444!
445!--    Count number of horizontal surfaces on local domain
446       DO  i = nxl, nxr
447          DO  j = nys, nyn
448             DO  k = nzb+1, nzt
449!
450!--             Check if current gridpoint belongs to the atmosphere
451                IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
452!
453!--                Check if grid point adjoins to any upward-facing horizontal
454!--                surface, e.g. the Earth surface, plane roofs, or ceilings.
455                   IF ( .NOT. BTEST( wall_flags_0(k-1,j,i), 0 ) )  THEN
456!
457!--                   Land-surface type
458                      IF ( land_surface )  THEN
459                         num_lsm_h    = num_lsm_h    + 1 
460!
461!--                   Urban surface tpye
462                      ELSEIF ( urban_surface )  THEN
463                         num_usm_h    = num_usm_h    + 1 
464!
465!--                   Default-surface type
466                      ELSE
467                         num_def_h(0) = num_def_h(0) + 1 
468                      ENDIF
469
470                   ENDIF
471!
472!--                Check for top-fluxes
473                   IF ( k == nzt  .AND.  use_top_fluxes )  THEN
474                      num_def_h(2) = num_def_h(2) + 1
475!
476!--                Check for any other downward-facing surface. So far only for
477!--                default surface type.
478                   ELSEIF ( .NOT. BTEST( wall_flags_0(k+1,j,i), 0 ) )  THEN
479                      num_def_h(1) = num_def_h(1) + 1
480                   ENDIF
481
482                ENDIF
483             ENDDO
484          ENDDO
485       ENDDO
486!
487!--    Count number of vertical surfaces on local domain
488       DO  i = nxl, nxr
489          DO  j = nys, nyn
490             DO  k = nzb+1, nzt
491                IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
492!
493!--                Northward-facing
494                   IF ( .NOT. BTEST( wall_flags_0(k,j-1,i), 0 ) )  THEN
495                      IF ( urban_surface )  THEN
496                         num_usm_v(0) = num_usm_v(0) + 1 
497                      ELSEIF ( land_surface )  THEN
498                         num_lsm_v(0) = num_lsm_v(0) + 1 
499                      ELSE
500                         num_def_v(0) = num_def_v(0) + 1 
501                      ENDIF
502                   ENDIF
503!
504!--                Southward-facing
505                   IF ( .NOT. BTEST( wall_flags_0(k,j+1,i), 0 ) )  THEN
506                      IF ( urban_surface )  THEN
507                         num_usm_v(1) = num_usm_v(1) + 1 
508                      ELSEIF ( land_surface )  THEN
509                         num_lsm_v(1) = num_lsm_v(1) + 1 
510                      ELSE
511                         num_def_v(1) = num_def_v(1) + 1 
512                      ENDIF
513                   ENDIF
514!
515!--                Eastward-facing
516                   IF ( .NOT. BTEST( wall_flags_0(k,j,i-1), 0 ) )  THEN
517                      IF ( urban_surface )  THEN
518                         num_usm_v(2) = num_usm_v(2) + 1 
519                      ELSEIF ( land_surface )  THEN
520                         num_lsm_v(2) = num_lsm_v(2) + 1 
521                      ELSE
522                         num_def_v(2) = num_def_v(2) + 1 
523                      ENDIF
524                   ENDIF
525!
526!--                Westward-facing
527                   IF ( .NOT. BTEST( wall_flags_0(k,j,i+1), 0 ) )  THEN
528                      IF ( urban_surface )  THEN
529                         num_usm_v(3) = num_usm_v(3) + 1
530                      ELSEIF ( land_surface )  THEN
531                         num_lsm_v(3) = num_lsm_v(3) + 1 
532                      ELSE
533                         num_def_v(3) = num_def_v(3) + 1 
534                      ENDIF
535                   ENDIF
536                ENDIF
537             ENDDO
538          ENDDO
539       ENDDO
540
541!
542!--    Store number of surfaces per core.
543!--    Horizontal surface, default type, upward facing
544       surf_def_h(0)%ns = num_def_h(0)
545!
546!--    Horizontal surface, default type, downward facing
547       surf_def_h(1)%ns = num_def_h(1)
548!
549!--    Horizontal surface, default type, top downward facing
550       surf_def_h(2)%ns = num_def_h(2)
551!
552!--    Horizontal surface, natural type, so far only upward-facing
553       surf_lsm_h%ns    = num_lsm_h 
554!
555!--    Horizontal surface, urban type, so far only upward-facing
556       surf_usm_h%ns    = num_usm_h   
557!
558!--    Vertical surface, default type, northward facing
559       surf_def_v(0)%ns = num_def_v(0)
560!
561!--    Vertical surface, default type, southward facing
562       surf_def_v(1)%ns = num_def_v(1)
563!
564!--    Vertical surface, default type, eastward facing
565       surf_def_v(2)%ns = num_def_v(2)
566!
567!--    Vertical surface, default type, westward facing
568       surf_def_v(3)%ns = num_def_v(3)
569!
570!--    Vertical surface, natural type, northward facing
571       surf_lsm_v(0)%ns = num_lsm_v(0)
572!
573!--    Vertical surface, natural type, southward facing
574       surf_lsm_v(1)%ns = num_lsm_v(1)
575!
576!--    Vertical surface, natural type, eastward facing
577       surf_lsm_v(2)%ns = num_lsm_v(2)
578!
579!--    Vertical surface, natural type, westward facing
580       surf_lsm_v(3)%ns = num_lsm_v(3)
581!
582!--    Vertical surface, urban type, northward facing
583       surf_usm_v(0)%ns = num_usm_v(0)
584!
585!--    Vertical surface, urban type, southward facing
586       surf_usm_v(1)%ns = num_usm_v(1)
587!
588!--    Vertical surface, urban type, eastward facing
589       surf_usm_v(2)%ns = num_usm_v(2)
590!
591!--    Vertical surface, urban type, westward facing
592       surf_usm_v(3)%ns = num_usm_v(3)
593!
594!--    Allocate required attributes for horizontal surfaces - default type.
595!--    Upward-facing (l=0) and downward-facing (l=1).
596       DO  l = 0, 1
597          CALL allocate_surface_attributes_h ( surf_def_h(l), nys, nyn, nxl, nxr )
598       ENDDO
599!
600!--    Allocate required attributes for model top
601       CALL allocate_surface_attributes_h_top ( surf_def_h(2), nys, nyn, nxl, nxr )
602!
603!--    Allocate required attributes for horizontal surfaces - natural type.
604       CALL allocate_surface_attributes_h ( surf_lsm_h, nys, nyn, nxl, nxr )
605!
606!--    Allocate required attributes for horizontal surfaces - urban type.
607       CALL allocate_surface_attributes_h ( surf_usm_h, nys, nyn, nxl, nxr )
608
609!
610!--    Allocate required attributes for vertical surfaces.
611!--    Northward-facing (l=0), southward-facing (l=1), eastward-facing (l=2)
612!--    and westward-facing (l=3).
613!--    Default type.
614       DO  l = 0, 3
615          CALL allocate_surface_attributes_v ( surf_def_v(l), .FALSE.,         &
616                                               nys, nyn, nxl, nxr )
617       ENDDO
618!
619!--    Natural type
620       DO  l = 0, 3
621          CALL allocate_surface_attributes_v ( surf_lsm_v(l), .TRUE.,          &
622                                               nys, nyn, nxl, nxr )
623       ENDDO
624!
625!--    Urban type
626       DO  l = 0, 3
627          CALL allocate_surface_attributes_v ( surf_usm_v(l), .FALSE.,         &
628                                               nys, nyn, nxl, nxr )
629       ENDDO
630
631    END SUBROUTINE init_surface_arrays
632
633!------------------------------------------------------------------------------!
634! Description:
635! ------------
636!> Allocating memory for upward and downward-facing horizontal surface types,
637!> except for top fluxes.
638!------------------------------------------------------------------------------!
639    SUBROUTINE allocate_surface_attributes_h( surfaces,                        &
640                                              nys_l, nyn_l, nxl_l, nxr_l )
641
642       IMPLICIT NONE
643
644       INTEGER(iwp) ::  nyn_l  !< north bound of local 2d array start/end_index, is equal to nyn, except for restart-array
645       INTEGER(iwp) ::  nys_l  !< south bound of local 2d array start/end_index, is equal to nyn, except for restart-array
646       INTEGER(iwp) ::  nxl_l  !< west bound of local 2d array start/end_index, is equal to nyn, except for restart-array
647       INTEGER(iwp) ::  nxr_l  !< east bound of local 2d array start/end_index, is equal to nyn, except for restart-array
648
649       TYPE(surf_type) ::  surfaces  !< respective surface type
650
651!
652!--    Allocate arrays for start and end index of horizontal surface type
653!--    for each (j,i)-grid point. This is required e.g. in diffion_x, which is
654!--    called for each (j,i). In order to find the location where the
655!--    respective flux is store within the surface-type, start- and end-
656!--    index are stored for each (j,i). For example, each (j,i) can have
657!--    several entries where fluxes for horizontal surfaces might be stored,
658!--    e.g. for overhanging structures where several upward-facing surfaces
659!--    might exist for given (j,i).
660!--    If no surface of respective type exist at current (j,i), set indicies
661!--    such that loop in diffusion routines will not be entered.
662       ALLOCATE ( surfaces%start_index(nys_l:nyn_l,nxl_l:nxr_l) )
663       ALLOCATE ( surfaces%end_index(nys_l:nyn_l,nxl_l:nxr_l)   )
664       surfaces%start_index = 0
665       surfaces%end_index   = -1
666!
667!--    Indices to locate surface element
668       ALLOCATE ( surfaces%i(1:surfaces%ns)  )
669       ALLOCATE ( surfaces%j(1:surfaces%ns)  )
670       ALLOCATE ( surfaces%k(1:surfaces%ns)  )
671!
672!--    Surface-layer height
673       ALLOCATE ( surfaces%z_mo(1:surfaces%ns) )
674!
675!--    Surface orientation
676       ALLOCATE ( surfaces%facing(1:surfaces%ns) )
677!
678!--    Surface-parallel wind velocity
679       ALLOCATE ( surfaces%uvw_abs(1:surfaces%ns) )
680!      ALLOCATE ( surfaces%pt_surface(1:surfaces%ns) )
681!
682!--    Roughness
683       ALLOCATE ( surfaces%z0(1:surfaces%ns)  )
684       ALLOCATE ( surfaces%z0h(1:surfaces%ns) )
685       ALLOCATE ( surfaces%z0q(1:surfaces%ns) )
686!
687!--    Friction velocity
688       ALLOCATE ( surfaces%us(1:surfaces%ns) )
689!
690!--    Stability parameter
691       ALLOCATE ( surfaces%ol(1:surfaces%ns) )
692!
693!--    Bulk Richardson number
694       ALLOCATE ( surfaces%rib(1:surfaces%ns) )
695!
696!--    Vertical momentum fluxes of u and v
697       ALLOCATE ( surfaces%usws(1:surfaces%ns) ) 
698       ALLOCATE ( surfaces%vsws(1:surfaces%ns) ) 
699!
700!--    Required in production_e
701       IF ( .NOT. constant_diffusion )  THEN   
702          ALLOCATE ( surfaces%u_0(1:surfaces%ns) ) 
703          ALLOCATE ( surfaces%v_0(1:surfaces%ns) )
704       ENDIF 
705!
706!--    Characteristic temperature and surface flux of sensible heat
707       ALLOCATE ( surfaces%ts(1:surfaces%ns)  )   
708       ALLOCATE ( surfaces%shf(1:surfaces%ns) )   
709!
710!--    Characteristic humidity and surface flux of latent heat
711       IF ( humidity )  THEN
712          ALLOCATE ( surfaces%qs(1:surfaces%ns)   ) 
713          ALLOCATE ( surfaces%qsws(1:surfaces%ns) )     
714       ENDIF 
715!
716!--    Characteristic scalar and surface flux of scalar
717       IF ( passive_scalar )  THEN
718          ALLOCATE ( surfaces%ss(1:surfaces%ns)   )   
719          ALLOCATE ( surfaces%ssws(1:surfaces%ns) ) 
720       ENDIF 
721!
722!--    When cloud physics is used, arrays for storing potential temperature and
723!--    specific humidity at first grid level are required.
724       IF ( cloud_physics )  THEN
725          ALLOCATE ( surfaces%pt1(1:surfaces%ns) )
726          ALLOCATE ( surfaces%qv1(1:surfaces%ns) )
727       ENDIF
728!
729!--       
730       IF ( cloud_physics .AND. microphysics_morrison)  THEN
731          ALLOCATE ( surfaces%qcs(1:surfaces%ns)   )
732          ALLOCATE ( surfaces%ncs(1:surfaces%ns)   )
733          ALLOCATE ( surfaces%qcsws(1:surfaces%ns) )
734          ALLOCATE ( surfaces%ncsws(1:surfaces%ns) )
735       ENDIF
736!
737!--       
738       IF ( cloud_physics .AND. microphysics_seifert)  THEN
739          ALLOCATE ( surfaces%qrs(1:surfaces%ns)   )
740          ALLOCATE ( surfaces%nrs(1:surfaces%ns)   )
741          ALLOCATE ( surfaces%qrsws(1:surfaces%ns) )
742          ALLOCATE ( surfaces%nrsws(1:surfaces%ns) )
743       ENDIF
744!
745!--    Salinity surface flux
746       IF ( ocean )  ALLOCATE ( surfaces%sasws(1:surfaces%ns) )
747
748    END SUBROUTINE allocate_surface_attributes_h
749
750
751!------------------------------------------------------------------------------!
752! Description:
753! ------------
754!> Allocating memory for model-top fluxes 
755!------------------------------------------------------------------------------!
756    SUBROUTINE allocate_surface_attributes_h_top( surfaces,                    &
757                                                  nys_l, nyn_l, nxl_l, nxr_l )
758
759       IMPLICIT NONE
760
761       INTEGER(iwp) ::  nyn_l  !< north bound of local 2d array start/end_index, is equal to nyn, except for restart-array
762       INTEGER(iwp) ::  nys_l  !< south bound of local 2d array start/end_index, is equal to nyn, except for restart-array
763       INTEGER(iwp) ::  nxl_l  !< west bound of local 2d array start/end_index, is equal to nyn, except for restart-array
764       INTEGER(iwp) ::  nxr_l  !< east bound of local 2d array start/end_index, is equal to nyn, except for restart-array
765
766       TYPE(surf_type) ::  surfaces !< respective surface type
767
768       ALLOCATE ( surfaces%start_index(nys_l:nyn_l,nxl_l:nxr_l) )
769       ALLOCATE ( surfaces%end_index(nys_l:nyn_l,nxl_l:nxr_l)   )
770       surfaces%start_index = 0
771       surfaces%end_index   = -1
772!
773!--    Indices to locate surface (model-top) element
774       ALLOCATE ( surfaces%i(1:surfaces%ns)  )
775       ALLOCATE ( surfaces%j(1:surfaces%ns)  )
776       ALLOCATE ( surfaces%k(1:surfaces%ns)  )
777!
778!--    Vertical momentum fluxes of u and v
779       ALLOCATE ( surfaces%usws(1:surfaces%ns) ) 
780       ALLOCATE ( surfaces%vsws(1:surfaces%ns) ) 
781!
782!--    Sensible heat flux
783       ALLOCATE ( surfaces%shf(1:surfaces%ns) )   
784!
785!--    Latent heat flux
786       IF ( humidity )  THEN
787          ALLOCATE ( surfaces%qsws(1:surfaces%ns) )     
788       ENDIF 
789!
790!--    Scalar flux
791       IF ( passive_scalar )  THEN
792          ALLOCATE ( surfaces%ssws(1:surfaces%ns) ) 
793       ENDIF 
794!
795!--       
796       IF ( cloud_physics .AND. microphysics_morrison)  THEN
797          ALLOCATE ( surfaces%qcsws(1:surfaces%ns) )
798          ALLOCATE ( surfaces%ncsws(1:surfaces%ns) )
799       ENDIF
800!
801!--       
802       IF ( cloud_physics .AND. microphysics_seifert)  THEN
803          ALLOCATE ( surfaces%qrsws(1:surfaces%ns) )
804          ALLOCATE ( surfaces%nrsws(1:surfaces%ns) )
805       ENDIF
806!
807!--    Salinity flux
808       IF ( ocean )  ALLOCATE ( surfaces%sasws(1:surfaces%ns) )
809
810    END SUBROUTINE allocate_surface_attributes_h_top
811
812!------------------------------------------------------------------------------!
813! Description:
814! ------------
815!> Allocating memory for vertical surface types.
816!------------------------------------------------------------------------------!
817    SUBROUTINE allocate_surface_attributes_v( surfaces, lsm,                   &
818                                              nys_l, nyn_l, nxl_l, nxr_l )
819
820       IMPLICIT NONE
821
822       INTEGER(iwp) ::  nyn_l  !< north bound of local 2d array start/end_index, is equal to nyn, except for restart-array
823       INTEGER(iwp) ::  nys_l  !< south bound of local 2d array start/end_index, is equal to nyn, except for restart-array
824       INTEGER(iwp) ::  nxl_l  !< west bound of local 2d array start/end_index, is equal to nyn, except for restart-array
825       INTEGER(iwp) ::  nxr_l  !< east bound of local 2d array start/end_index, is equal to nyn, except for restart-array
826
827       LOGICAL         ::  lsm      !< flag indicating data type of natural land surface
828
829       TYPE(surf_type) ::  surfaces !< respective surface type
830
831!
832!--    Allocate arrays for start and end index of vertical surface type
833!--    for each (j,i)-grid point. This is required in diffion_x, which is
834!--    called for each (j,i). In order to find the location where the
835!--    respective flux is store within the surface-type, start- and end-
836!--    index are stored for each (j,i). For example, each (j,i) can have
837!--    several entries where fluxes for vertical surfaces might be stored. 
838!--    In the flat case, where no vertical walls exit, set indicies such
839!--    that loop in diffusion routines will not be entered.
840       ALLOCATE ( surfaces%start_index(nys_l:nyn_l,nxl_l:nxr_l) )
841       ALLOCATE ( surfaces%end_index(nys_l:nyn_l,nxl_l:nxr_l)   )
842       surfaces%start_index = 0
843       surfaces%end_index   = -1
844!
845!--    Indices to locate surface element.
846       ALLOCATE ( surfaces%i(1:surfaces%ns) )
847       ALLOCATE ( surfaces%j(1:surfaces%ns) )
848       ALLOCATE ( surfaces%k(1:surfaces%ns) )
849!
850!--    Surface-layer height
851       ALLOCATE ( surfaces%z_mo(1:surfaces%ns) )
852!
853!--    Surface orientation
854       ALLOCATE ( surfaces%facing(1:surfaces%ns) )
855!
856!--    Surface parallel wind velocity
857       ALLOCATE ( surfaces%uvw_abs(1:surfaces%ns) )
858!
859!--    Roughness
860       ALLOCATE ( surfaces%z0(1:surfaces%ns)  )
861       ALLOCATE ( surfaces%z0h(1:surfaces%ns) )
862       ALLOCATE ( surfaces%z0q(1:surfaces%ns) )
863
864!
865!--    Friction velocity
866       ALLOCATE ( surfaces%us(1:surfaces%ns) )
867!
868!--    Allocate Obukhov length and bulk Richardson number. Only required
869!--    for natural land surfaces
870       IF ( lsm )  THEN
871          ALLOCATE( surfaces%ol(1:surfaces%ns)  ) 
872          ALLOCATE( surfaces%rib(1:surfaces%ns) ) 
873       ENDIF
874!
875!--    Allocate arrays for surface momentum fluxes for u and v. For u at north-
876!--    and south-facing surfaces, for v at east- and west-facing surfaces.
877       ALLOCATE ( surfaces%mom_flux_uv(1:surfaces%ns) )
878!
879!--    Allocate array for surface momentum flux for w - wsus and wsvs
880       ALLOCATE ( surfaces%mom_flux_w(1:surfaces%ns) ) 
881!
882!--    Allocate array for surface momentum flux for subgrid-scale tke wsus and
883!--    wsvs; first index usvs or vsws, second index for wsus or wsvs, depending
884!--    on surface.
885       ALLOCATE ( surfaces%mom_flux_tke(0:1,1:surfaces%ns) ) 
886!
887!--    Characteristic temperature and surface flux of sensible heat
888       ALLOCATE ( surfaces%ts(1:surfaces%ns)  )   
889       ALLOCATE ( surfaces%shf(1:surfaces%ns) )   
890!
891!--    Characteristic humidity and surface flux of latent heat
892       IF ( humidity )  THEN
893          ALLOCATE ( surfaces%qs(1:surfaces%ns)   ) 
894          ALLOCATE ( surfaces%qsws(1:surfaces%ns) )     
895       ENDIF 
896!
897!--    Characteristic scalar and surface flux of scalar
898       IF ( passive_scalar )  THEN
899          ALLOCATE ( surfaces%ss(1:surfaces%ns)   )   
900          ALLOCATE ( surfaces%ssws(1:surfaces%ns) ) 
901       ENDIF
902
903       IF ( cloud_physics .AND. microphysics_seifert)  THEN
904          ALLOCATE ( surfaces%qcs(1:surfaces%ns)   )
905          ALLOCATE ( surfaces%ncs(1:surfaces%ns)   )
906          ALLOCATE ( surfaces%qcsws(1:surfaces%ns) )
907          ALLOCATE ( surfaces%ncsws(1:surfaces%ns) )
908       ENDIF
909
910       IF ( cloud_physics .AND. microphysics_seifert)  THEN
911          ALLOCATE ( surfaces%qrs(1:surfaces%ns)   )
912          ALLOCATE ( surfaces%nrs(1:surfaces%ns)   )
913          ALLOCATE ( surfaces%qrsws(1:surfaces%ns) )
914          ALLOCATE ( surfaces%nrsws(1:surfaces%ns) )
915       ENDIF
916!
917!--    Salinity surface flux
918       IF ( ocean )  ALLOCATE ( surfaces%sasws(1:surfaces%ns) )
919
920    END SUBROUTINE allocate_surface_attributes_v
921
922!------------------------------------------------------------------------------!
923! Description:
924! ------------
925!> Initialize surface elements.
926!------------------------------------------------------------------------------!
927    SUBROUTINE init_surfaces
928
929       IMPLICIT NONE
930
931       INTEGER(iwp) ::  i         !< running index x-direction
932       INTEGER(iwp) ::  j         !< running index y-direction
933       INTEGER(iwp) ::  k         !< running index z-direction
934       INTEGER(iwp) ::  l         !< index variable used to distinguish surface facing
935       INTEGER(iwp) ::  m         !< running index surface elements
936
937       INTEGER(iwp)                 ::  start_index_lsm_h !< dummy to determing local start index in surface type for given (j,i), for horizontal natural surfaces
938       INTEGER(iwp)                 ::  start_index_usm_h !< dummy to determing local start index in surface type for given (j,i), for horizontal urban surfaces
939
940       INTEGER(iwp)                 ::  num_lsm_h     !< current number of horizontal surface element, natural type
941       INTEGER(iwp)                 ::  num_lsm_h_kji !< dummy to determing local end index in surface type for given (j,i), for for horizonal natural surfaces
942       INTEGER(iwp)                 ::  num_usm_h     !< current number of horizontal surface element, urban type
943       INTEGER(iwp)                 ::  num_usm_h_kji !< dummy to determing local end index in surface type for given (j,i), for for horizonal urban surfaces
944
945       INTEGER(iwp), DIMENSION(0:2) ::  num_def_h     !< current number of horizontal surface element, default type
946       INTEGER(iwp), DIMENSION(0:2) ::  num_def_h_kji !< dummy to determing local end index in surface type for given (j,i), for horizonal default surfaces
947       INTEGER(iwp), DIMENSION(0:2) ::  start_index_def_h !< dummy to determing local start index in surface type for given (j,i), for horizontal default surfaces
948     
949       INTEGER(iwp), DIMENSION(0:3) ::  num_def_v     !< current number of vertical surface element, default type
950       INTEGER(iwp), DIMENSION(0:3) ::  num_def_v_kji !< dummy to determing local end index in surface type for given (j,i), for vertical default surfaces
951       INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v     !< current number of vertical surface element, natural type
952       INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v_kji !< dummy to determing local end index in surface type for given (j,i), for vertical natural surfaces
953       INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v     !< current number of vertical surface element, urban type
954       INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v_kji !< dummy to determing local end index in surface type for given (j,i), for vertical urban surfaces
955
956       INTEGER(iwp), DIMENSION(0:3) ::  start_index_def_v !< dummy to determing local start index in surface type for given (j,i), for vertical default surfaces
957       INTEGER(iwp), DIMENSION(0:3) ::  start_index_lsm_v !< dummy to determing local start index in surface type for given (j,i), for vertical natural surfaces
958       INTEGER(iwp), DIMENSION(0:3) ::  start_index_usm_v !< dummy to determing local start index in surface type for given (j,i), for vertical urban surfaces
959
960
961!
962!--    Initialize surface attributes, store indicies, surfaces orientation, etc.,
963       num_def_h(0:2) = 1
964       num_def_v(0:3) = 1
965
966       num_lsm_h      = 1
967       num_lsm_v(0:3) = 1
968
969       num_usm_h      = 1
970       num_usm_v(0:3) = 1
971
972       start_index_def_h(0:2) = 1
973       start_index_def_v(0:3) = 1
974
975       start_index_lsm_h      = 1
976       start_index_lsm_v(0:3) = 1
977
978       start_index_usm_h      = 1
979       start_index_usm_v(0:3) = 1
980
981       DO  i = nxl, nxr
982          DO  j = nys, nyn
983
984             num_def_h_kji = 0
985             num_def_v_kji = 0
986             num_lsm_h_kji = 0
987             num_lsm_v_kji = 0
988             num_usm_h_kji = 0
989             num_usm_v_kji = 0
990
991             DO  k = nzb+1, nzt
992!
993!--             Check if current gridpoint belongs to the atmosphere
994                IF ( BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
995!
996!--                Upward-facing surface. Distinguish between differet surface types.
997!--                To do, think about method to flag natural and non-natural
998!--                surfaces. Only to ask for land_surface or urban surface
999!--                is just a work-around.
1000                   IF ( .NOT. BTEST( wall_flags_0(k-1,j,i), 0 ) )  THEN 
1001!
1002!--                   Natural surface type         
1003                      IF ( land_surface )  THEN
1004                         CALL initialize_horizontal_surfaces( k, j, i,         &
1005                                                              surf_lsm_h,      &
1006                                                              num_lsm_h,       &
1007                                                              num_lsm_h_kji,   &
1008                                                              .TRUE., .FALSE. ) 
1009!
1010!--                   Urban surface tpye
1011                      ELSEIF ( urban_surface )  THEN
1012                         CALL initialize_horizontal_surfaces( k, j, i,         &
1013                                                              surf_usm_h,      &
1014                                                              num_usm_h,       &
1015                                                              num_usm_h_kji,   &
1016                                                              .TRUE., .FALSE. ) 
1017!
1018!--                   Default surface type
1019                      ELSE
1020                         CALL initialize_horizontal_surfaces( k, j, i,         &
1021                                                              surf_def_h(0),   &
1022                                                              num_def_h(0),    &
1023                                                              num_def_h_kji(0),&
1024                                                              .TRUE., .FALSE. ) 
1025                      ENDIF
1026                   ENDIF 
1027!
1028!--                downward-facing surface, first, model top
1029                   IF ( k == nzt  .AND.  use_top_fluxes )  THEN
1030                      CALL initialize_top( k, j, i, surf_def_h(2),             &
1031                                           num_def_h(2), num_def_h_kji(2) )
1032!
1033!--                Check for any other downward-facing surface. So far only for
1034!--                default surface type.
1035                   ELSEIF ( .NOT. BTEST( wall_flags_0(k+1,j,i), 0 ) )  THEN
1036                      CALL initialize_horizontal_surfaces( k, j, i,            &
1037                                                           surf_def_h(1),      &
1038                                                           num_def_h(1),       &
1039                                                           num_def_h_kji(1),   &
1040                                                           .FALSE., .TRUE. )   
1041                   ENDIF 
1042!
1043!--                Check for vertical walls and, if required, initialize it.
1044!                  Start with northward-facing surface.
1045                   IF ( .NOT. BTEST( wall_flags_0(k,j-1,i), 0 ) )  THEN
1046                      IF ( urban_surface )  THEN
1047                         CALL initialize_vertical_surfaces( 0, k, j, i,        &
1048                                                            surf_usm_v(0),     &
1049                                                            num_usm_v(0),      &
1050                                                            num_usm_v_kji(0),  &
1051                                                            .FALSE., .FALSE.,  &             
1052                                                            .FALSE., .TRUE. ) 
1053                      ELSEIF ( land_surface )  THEN
1054                         CALL initialize_vertical_surfaces( 0, k, j, i,        &
1055                                                            surf_lsm_v(0),     &
1056                                                            num_lsm_v(0),      &
1057                                                            num_lsm_v_kji(0),  &
1058                                                            .FALSE., .FALSE.,  &             
1059                                                            .FALSE., .TRUE. ) 
1060                      ELSE
1061                         CALL initialize_vertical_surfaces( 0, k, j, i,        &
1062                                                            surf_def_v(0),     &
1063                                                            num_def_v(0),      &
1064                                                            num_def_v_kji(0),  &
1065                                                            .FALSE., .FALSE.,  &             
1066                                                            .FALSE., .TRUE. ) 
1067                      ENDIF
1068                   ENDIF
1069!
1070!--                southward-facing surface
1071                   IF ( .NOT. BTEST( wall_flags_0(k,j+1,i), 0 ) )  THEN
1072                      IF ( urban_surface )  THEN
1073                         CALL initialize_vertical_surfaces( 1, k, j, i,        &
1074                                                            surf_usm_v(1),     &
1075                                                            num_usm_v(1),      &
1076                                                            num_usm_v_kji(1),  &
1077                                                            .FALSE., .FALSE.,  &
1078                                                            .TRUE., .FALSE. )
1079                      ELSEIF ( land_surface )  THEN
1080                         CALL initialize_vertical_surfaces( 1, k, j, i,        &
1081                                                            surf_lsm_v(1),     &
1082                                                            num_lsm_v(1),      &
1083                                                            num_lsm_v_kji(1),  &
1084                                                            .FALSE., .FALSE.,  &
1085                                                            .TRUE., .FALSE. ) 
1086                      ELSE
1087                         CALL initialize_vertical_surfaces( 1, k, j, i,        &
1088                                                            surf_def_v(1),     &
1089                                                            num_def_v(1),      &
1090                                                            num_def_v_kji(1),  &
1091                                                            .FALSE., .FALSE.,  &
1092                                                            .TRUE., .FALSE. ) 
1093                      ENDIF
1094                   ENDIF
1095!
1096!--                eastward-facing surface
1097                   IF ( .NOT. BTEST( wall_flags_0(k,j,i-1), 0 ) )  THEN
1098                      IF ( urban_surface )  THEN
1099                         CALL initialize_vertical_surfaces( 2, k, j, i,        &
1100                                                            surf_usm_v(2),     &
1101                                                            num_usm_v(2),      &
1102                                                            num_usm_v_kji(2),  &
1103                                                            .TRUE., .FALSE.,   &
1104                                                            .FALSE., .FALSE. ) 
1105                      ELSEIF ( land_surface )  THEN
1106                         CALL initialize_vertical_surfaces( 2, k, j, i,        &
1107                                                            surf_lsm_v(2),     &
1108                                                            num_lsm_v(2),      &
1109                                                            num_lsm_v_kji(2),  &
1110                                                            .TRUE., .FALSE.,   &
1111                                                            .FALSE., .FALSE. ) 
1112                      ELSE
1113                         CALL initialize_vertical_surfaces( 2, k, j, i,        &
1114                                                            surf_def_v(2),     &
1115                                                            num_def_v(2),      &
1116                                                            num_def_v_kji(2),  &
1117                                                            .TRUE., .FALSE.,   &
1118                                                            .FALSE., .FALSE. ) 
1119                      ENDIF
1120                   ENDIF 
1121!   
1122!--                westward-facing surface
1123                   IF ( .NOT. BTEST( wall_flags_0(k,j,i+1), 0 ) )  THEN
1124                      IF ( urban_surface )  THEN
1125                         CALL initialize_vertical_surfaces( 3, k, j, i,        &
1126                                                            surf_usm_v(3),     &
1127                                                            num_usm_v(3),      &
1128                                                            num_usm_v_kji(3),  &
1129                                                           .FALSE., .TRUE.,    &
1130                                                           .FALSE., .FALSE. ) 
1131                      ELSEIF ( land_surface )  THEN
1132                         CALL initialize_vertical_surfaces( 3, k, j, i,        &
1133                                                            surf_lsm_v(3),     &
1134                                                            num_lsm_v(3),      &
1135                                                            num_lsm_v_kji(3),  &
1136                                                           .FALSE., .TRUE.,    &
1137                                                           .FALSE., .FALSE. ) 
1138                      ELSE
1139                         CALL initialize_vertical_surfaces( 3, k, j, i,        &
1140                                                            surf_def_v(3),     &
1141                                                            num_def_v(3),      &
1142                                                            num_def_v_kji(3),  &
1143                                                           .FALSE., .TRUE.,    &
1144                                                           .FALSE., .FALSE. ) 
1145                      ENDIF
1146                   ENDIF
1147                ENDIF
1148
1149 
1150             ENDDO
1151!
1152!--          Determine start- and end-index at grid point (j,i). Also, for
1153!--          horizontal surfaces more than 1 horizontal surface element can
1154!--          exist at grid point (j,i) if overhanging structures are present.
1155!--          Upward-facing surfaces
1156             surf_def_h(0)%start_index(j,i) = start_index_def_h(0)
1157             surf_def_h(0)%end_index(j,i)   = surf_def_h(0)%start_index(j,i) + &
1158                                                 num_def_h_kji(0) - 1
1159             start_index_def_h(0)           = surf_def_h(0)%end_index(j,i) + 1
1160!
1161!--          Downward-facing surfaces, except model top
1162             surf_def_h(1)%start_index(j,i) = start_index_def_h(1)                                                 
1163             surf_def_h(1)%end_index(j,i)   = surf_def_h(1)%start_index(j,i) + &
1164                                                 num_def_h_kji(1) - 1
1165             start_index_def_h(1)           = surf_def_h(1)%end_index(j,i) + 1
1166!
1167!--          Downward-facing surfaces -- model top fluxes
1168             surf_def_h(2)%start_index(j,i) = start_index_def_h(2)                                                 
1169             surf_def_h(2)%end_index(j,i)   = surf_def_h(2)%start_index(j,i) + &
1170                                                 num_def_h_kji(2) - 1
1171             start_index_def_h(2)           = surf_def_h(2)%end_index(j,i) + 1
1172!
1173!--          Horizontal natural land surfaces
1174             surf_lsm_h%start_index(j,i)    = start_index_lsm_h
1175             surf_lsm_h%end_index(j,i)      = surf_lsm_h%start_index(j,i) +    &
1176                                                 num_lsm_h_kji - 1
1177             start_index_lsm_h              = surf_lsm_h%end_index(j,i) + 1
1178!
1179!--          Horizontal urban surfaces
1180             surf_usm_h%start_index(j,i)    = start_index_usm_h
1181             surf_usm_h%end_index(j,i)      = surf_usm_h%start_index(j,i) +    &
1182                                                 num_usm_h_kji - 1
1183             start_index_usm_h              = surf_usm_h%end_index(j,i) + 1
1184
1185!
1186!--          Vertical surfaces - Default type
1187             surf_def_v(0)%start_index(j,i) = start_index_def_v(0)
1188             surf_def_v(1)%start_index(j,i) = start_index_def_v(1)
1189             surf_def_v(2)%start_index(j,i) = start_index_def_v(2)
1190             surf_def_v(3)%start_index(j,i) = start_index_def_v(3)
1191             surf_def_v(0)%end_index(j,i)   = start_index_def_v(0) +           & 
1192                                              num_def_v_kji(0) - 1
1193             surf_def_v(1)%end_index(j,i)   = start_index_def_v(1) +           &
1194                                              num_def_v_kji(1) - 1
1195             surf_def_v(2)%end_index(j,i)   = start_index_def_v(2) +           &
1196                                              num_def_v_kji(2) - 1
1197             surf_def_v(3)%end_index(j,i)   = start_index_def_v(3) +           &
1198                                              num_def_v_kji(3) - 1
1199             start_index_def_v(0)           = surf_def_v(0)%end_index(j,i) + 1
1200             start_index_def_v(1)           = surf_def_v(1)%end_index(j,i) + 1
1201             start_index_def_v(2)           = surf_def_v(2)%end_index(j,i) + 1
1202             start_index_def_v(3)           = surf_def_v(3)%end_index(j,i) + 1
1203!
1204!--          Natural type
1205             surf_lsm_v(0)%start_index(j,i) = start_index_lsm_v(0)
1206             surf_lsm_v(1)%start_index(j,i) = start_index_lsm_v(1)
1207             surf_lsm_v(2)%start_index(j,i) = start_index_lsm_v(2)
1208             surf_lsm_v(3)%start_index(j,i) = start_index_lsm_v(3)
1209             surf_lsm_v(0)%end_index(j,i)   = start_index_lsm_v(0) +           & 
1210                                              num_lsm_v_kji(0) - 1
1211             surf_lsm_v(1)%end_index(j,i)   = start_index_lsm_v(1) +           &
1212                                              num_lsm_v_kji(1) - 1
1213             surf_lsm_v(2)%end_index(j,i)   = start_index_lsm_v(2) +           &
1214                                              num_lsm_v_kji(2) - 1
1215             surf_lsm_v(3)%end_index(j,i)   = start_index_lsm_v(3) +           &
1216                                              num_lsm_v_kji(3) - 1
1217             start_index_lsm_v(0)           = surf_lsm_v(0)%end_index(j,i) + 1
1218             start_index_lsm_v(1)           = surf_lsm_v(1)%end_index(j,i) + 1
1219             start_index_lsm_v(2)           = surf_lsm_v(2)%end_index(j,i) + 1
1220             start_index_lsm_v(3)           = surf_lsm_v(3)%end_index(j,i) + 1
1221!
1222!--          Urban type
1223             surf_usm_v(0)%start_index(j,i) = start_index_usm_v(0)
1224             surf_usm_v(1)%start_index(j,i) = start_index_usm_v(1)
1225             surf_usm_v(2)%start_index(j,i) = start_index_usm_v(2)
1226             surf_usm_v(3)%start_index(j,i) = start_index_usm_v(3)
1227             surf_usm_v(0)%end_index(j,i)   = start_index_usm_v(0) +           & 
1228                                              num_usm_v_kji(0) - 1
1229             surf_usm_v(1)%end_index(j,i)   = start_index_usm_v(1) +           &
1230                                              num_usm_v_kji(1) - 1
1231             surf_usm_v(2)%end_index(j,i)   = start_index_usm_v(2) +           &
1232                                              num_usm_v_kji(2) - 1
1233             surf_usm_v(3)%end_index(j,i)   = start_index_usm_v(3) +           &
1234                                              num_usm_v_kji(3) - 1
1235             start_index_usm_v(0)           = surf_usm_v(0)%end_index(j,i) + 1
1236             start_index_usm_v(1)           = surf_usm_v(1)%end_index(j,i) + 1
1237             start_index_usm_v(2)           = surf_usm_v(2)%end_index(j,i) + 1
1238             start_index_usm_v(3)           = surf_usm_v(3)%end_index(j,i) + 1
1239
1240
1241          ENDDO
1242       ENDDO
1243
1244       CONTAINS
1245
1246!------------------------------------------------------------------------------!
1247! Description:
1248! ------------
1249!> Initialize horizontal surface elements, upward- and downward-facing.
1250!> Note, horizontal surface type alsw comprises model-top fluxes, which are,
1251!> initialized in a different routine.
1252!------------------------------------------------------------------------------!
1253          SUBROUTINE initialize_horizontal_surfaces( k, j, i, surf, num_h,     &
1254                                                     num_h_kji, upward_facing, &
1255                                                     downward_facing )       
1256
1257             IMPLICIT NONE
1258
1259             INTEGER(iwp)  ::  i                !< running index x-direction
1260             INTEGER(iwp)  ::  j                !< running index y-direction
1261             INTEGER(iwp)  ::  k                !< running index z-direction
1262             INTEGER(iwp)  ::  num_h            !< current number of surface element
1263             INTEGER(iwp)  ::  num_h_kji        !< dummy increment
1264
1265             LOGICAL       ::  upward_facing    !< flag indicating upward-facing surface
1266             LOGICAL       ::  downward_facing  !< flag indicating downward-facing surface
1267
1268             TYPE( surf_type ) :: surf          !< respective surface type
1269!
1270!--          Store indices of respective surface element
1271             surf%i(num_h) = i
1272             surf%j(num_h) = j
1273             surf%k(num_h) = k
1274!
1275!--          Surface orientation, bit 0 is set to 1 for upward-facing surfaces,
1276!--          bit 1 is for downward-facing surfaces.
1277             IF ( upward_facing   )  surf%facing(num_h) = IBSET( surf%facing(num_h), 0 )
1278             IF ( downward_facing )  surf%facing(num_h) = IBSET( surf%facing(num_h), 1 )
1279!
1280!--          Initialize surface-layer height
1281             IF ( upward_facing )  THEN
1282                surf%z_mo(num_h)  = zu(k) - zw(k-1)
1283             ELSE
1284                surf%z_mo(num_h)  = zw(k) - zu(k)
1285             ENDIF
1286 
1287             surf%z0(num_h)    = roughness_length
1288             surf%z0h(num_h)   = z0h_factor * roughness_length
1289             surf%z0q(num_h)   = z0h_factor * roughness_length         
1290!
1291!--          Initialization in case of 1D pre-cursor run
1292             IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )&
1293             THEN
1294                IF ( .NOT. constant_diffusion )  THEN
1295                   IF ( constant_flux_layer )  THEN
1296                      surf%ol(num_h)   = surf%z_mo(num_h) /                    &
1297                                            ( rif1d(nzb+1) + 1.0E-20_wp )
1298                      surf%us(num_h)   = us1d
1299                      surf%usws(num_h) = usws1d
1300                      surf%vsws(num_h) = vsws1d
1301                   ELSE
1302                      surf%ol(num_h)   = surf%z_mo(num_h) / zeta_min
1303                      surf%us(num_h)   = 0.0_wp
1304                      surf%usws(num_h) = 0.0_wp
1305                      surf%vsws(num_h) = 0.0_wp
1306                   ENDIF
1307                ELSE
1308                   surf%ol(num_h)   = surf%z_mo(num_h) / zeta_min
1309                   surf%us(num_h)   = 0.0_wp
1310                   surf%usws(num_h) = 0.0_wp
1311                   surf%vsws(num_h) = 0.0_wp
1312                ENDIF
1313!
1314!--          Initialization in case of constant profiles
1315             ELSEIF ( INDEX(initializing_actions, 'set_constant_profiles') /= 0 )&
1316             THEN
1317
1318                surf%ol(num_h)   = surf%z_mo(num_h) / zeta_min
1319!
1320!--             Very small number is required for calculation of Obukhov length
1321!--             at first timestep     
1322                surf%us(num_h)    = 1E-30_wp 
1323                surf%usws(num_h)  = 0.0_wp
1324                surf%vsws(num_h)  = 0.0_wp
1325       
1326             ENDIF
1327
1328             surf%rib(num_h)   = 0.0_wp 
1329             surf%uvw_abs(num_h) = 0.0_wp
1330
1331             IF ( .NOT. constant_diffusion )  THEN   
1332                surf%u_0(num_h)     = 0.0_wp 
1333                surf%v_0(num_h)     = 0.0_wp
1334             ENDIF
1335
1336             surf%ts(num_h)   = 0.0_wp
1337
1338             IF ( humidity )  THEN
1339                surf%qs(num_h)   = 0.0_wp
1340                IF ( cloud_physics .AND. microphysics_morrison)  THEN
1341                   surf%qcs(num_h) = 0.0_wp
1342                   surf%ncs(num_h) = 0.0_wp
1343   
1344                   surf%qcsws(num_h) = 0.0_wp
1345                   surf%ncsws(num_h) = 0.0_wp
1346
1347                ENDIF
1348                IF ( cloud_physics .AND. microphysics_seifert)  THEN
1349                   surf%qrs(num_h) = 0.0_wp
1350                   surf%nrs(num_h) = 0.0_wp
1351   
1352                   surf%qrsws(num_h) = 0.0_wp
1353                   surf%nrsws(num_h) = 0.0_wp
1354
1355                   surf%pt1(num_h) = 0.0_wp
1356                   surf%qv1(num_h) = 0.0_wp
1357
1358                ENDIF
1359             ENDIF
1360
1361             IF ( passive_scalar )  surf%ss(num_h) = 0.0_wp
1362!
1363!--          Inititalize surface fluxes of sensible and latent heat, as well as
1364!--          passive scalar
1365             IF ( use_surface_fluxes )  THEN
1366
1367                IF ( upward_facing )  THEN
1368                   IF ( constant_heatflux )  THEN
1369!   
1370!--                   Initialize surface heatflux. However, skip this for now if
1371!--                   if random_heatflux is set. This case, shf is initialized later.
1372                      IF ( .NOT. random_heatflux )  THEN
1373                         surf%shf(num_h) = surface_heatflux *               &
1374                                                 heatflux_input_conversion(nzb)
1375!
1376!--                      Check if surface heat flux might be replaced by
1377!--                      prescribed wall heatflux
1378                         IF ( k-1 /= 0 )  THEN
1379                            surf%shf(num_h) = wall_heatflux(0) *            &
1380                                                 heatflux_input_conversion(k-1)
1381                         ENDIF
1382!
1383!--                      Initialize shf with data from external file LSF_DATA. Will
1384!--                      be done directly in ls_foring_surf
1385!--                      Attention: Just a workaround, need to be revised!!!
1386                         IF ( large_scale_forcing .AND. lsf_surf )  THEN
1387!                             CALL ls_forcing_surf ( simulated_time )
1388!                             surf%shf(num_h) = shf(j,i) 
1389                         ENDIF
1390                      ENDIF
1391                   ELSE
1392                      surf%shf(num_h) = 0.0_wp
1393                   ENDIF
1394!
1395!--             Set heat-flux at downward-facing surfaces
1396                ELSE
1397                   surf%shf(num_h) = wall_heatflux(5) *                        &
1398                                             heatflux_input_conversion(k)
1399                ENDIF
1400
1401                IF ( humidity )  THEN
1402                   IF ( upward_facing )  THEN
1403                      IF ( constant_waterflux )  THEN
1404                         surf%qsws(num_h) = surface_waterflux *                &
1405                                                 waterflux_input_conversion(nzb)
1406                         IF ( k-1 /= 0 )  THEN
1407                            surf%qsws(num_h) = wall_humidityflux(0) *          &
1408                                                 waterflux_input_conversion(k-1)
1409                         ENDIF
1410                      ELSE
1411                         surf%qsws(num_h) = 0.0_wp
1412                      ENDIF
1413                   ELSE
1414                      surf%qsws(num_h) = wall_humidityflux(5) *                &
1415                                             heatflux_input_conversion(k)
1416                   ENDIF
1417                ENDIF
1418
1419                IF ( passive_scalar )  THEN
1420                   IF ( upward_facing )  THEN
1421                      IF ( constant_scalarflux )  THEN
1422                         surf%ssws(num_h) = surface_scalarflux
1423
1424                         IF ( k-1 /= 0 )                                       &
1425                            surf%ssws(num_h) = wall_scalarflux(0)
1426
1427                      ELSE
1428                         surf%ssws(num_h) = 0.0_wp
1429                      ENDIF
1430                   ELSE
1431                      surf%ssws(num_h) = wall_scalarflux(5)
1432                   ENDIF
1433                ENDIF
1434
1435                IF ( ocean )  THEN
1436                   IF ( upward_facing )  THEN
1437                      surf%sasws(num_h) = bottom_salinityflux
1438                   ELSE
1439                      surf%sasws(num_h) = 0.0_wp
1440                   ENDIF
1441                ENDIF
1442             ENDIF
1443!
1444!--          Increment surface indices
1445             num_h     = num_h + 1
1446             num_h_kji = num_h_kji + 1     
1447
1448
1449          END SUBROUTINE initialize_horizontal_surfaces
1450       
1451
1452!------------------------------------------------------------------------------!
1453! Description:
1454! ------------
1455!> Initialize model-top fluxes. Currently, only the heatflux and salinity flux
1456!> can be prescribed, latent flux is zero in this case!
1457!------------------------------------------------------------------------------!
1458          SUBROUTINE initialize_top( k, j, i, surf, num_h, num_h_kji )       
1459
1460             IMPLICIT NONE
1461
1462             INTEGER(iwp)  ::  i                !< running index x-direction
1463             INTEGER(iwp)  ::  j                !< running index y-direction
1464             INTEGER(iwp)  ::  k                !< running index z-direction
1465             INTEGER(iwp)  ::  num_h            !< current number of surface element
1466             INTEGER(iwp)  ::  num_h_kji        !< dummy increment
1467
1468             TYPE( surf_type ) :: surf          !< respective surface type
1469!
1470!--          Store indices of respective surface element
1471             surf%i(num_h) = i
1472             surf%j(num_h) = j
1473             surf%k(num_h) = k
1474!
1475!--          Initialize top heat flux
1476             IF ( constant_top_heatflux )                                      &
1477                surf%shf = top_heatflux * heatflux_input_conversion(nzt+1)
1478!
1479!--          Initialization in case of a coupled model run
1480             IF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1481                surf%shf = 0.0_wp
1482             ENDIF
1483!
1484!--          Prescribe latent heat flux at the top     
1485             IF ( humidity )  THEN
1486             surf%qsws = 0.0_wp
1487                IF ( cloud_physics  .AND.  microphysics_morrison ) THEN
1488                   surf%ncsws = 0.0_wp
1489                   surf%qcsws = 0.0_wp
1490                ENDIF
1491                IF ( cloud_physics  .AND.  microphysics_seifert ) THEN
1492                   surf%nrsws = 0.0_wp
1493                   surf%qrsws = 0.0_wp
1494                ENDIF
1495             ENDIF
1496!
1497!--          Prescribe top scalar flux
1498             IF ( passive_scalar .AND. constant_top_scalarflux )               &
1499                surf%ssws = top_scalarflux
1500!
1501!--          Prescribe top salinity flux
1502             IF ( ocean .AND. constant_top_salinityflux)                          &
1503                surf%sasws = top_salinityflux
1504!
1505!--          Initialization in case of a coupled model run
1506             IF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
1507                surf%shf = 0.0_wp
1508             ENDIF
1509!
1510!--          Top momentum fluxes
1511             surf%usws = top_momentumflux_u * momentumflux_input_conversion(nzt+1)
1512             surf%vsws = top_momentumflux_v * momentumflux_input_conversion(nzt+1)
1513!
1514!--          Increment surface indices
1515             num_h     = num_h + 1
1516             num_h_kji = num_h_kji + 1     
1517
1518
1519          END SUBROUTINE initialize_top
1520
1521
1522!------------------------------------------------------------------------------!
1523! Description:
1524! ------------
1525!> Initialize vertical surface elements.
1526!------------------------------------------------------------------------------!
1527          SUBROUTINE initialize_vertical_surfaces( l, k, j, i, surf, num_v,    &
1528                                                num_v_kji, east_facing,        &
1529                                                west_facing, south_facing,     &
1530                                                north_facing )       
1531
1532             IMPLICIT NONE
1533
1534             INTEGER(iwp)  ::  component !<
1535             INTEGER(iwp)  ::  i               !< running index x-direction
1536             INTEGER(iwp)  ::  j               !< running index x-direction
1537             INTEGER(iwp)  ::  k               !< running index x-direction
1538             INTEGER(iwp)  ::  l               !< index variable for the surface type, indicating the facing
1539             INTEGER(iwp)  ::  num_v           !< current number of surface element
1540             INTEGER(iwp)  ::  num_v_kji       !< current number of surface element at (j,i)
1541
1542
1543             LOGICAL       ::  east_facing     !< flag indicating east-facing surfaces
1544             LOGICAL       ::  north_facing    !< flag indicating north-facing surfaces
1545             LOGICAL       ::  south_facing    !< flag indicating south-facing surfaces
1546             LOGICAL       ::  west_facing     !< flag indicating west-facing surfaces
1547
1548             TYPE( surf_type ) :: surf         !< respective surface type
1549
1550!
1551!--          Store indices of respective wall element
1552             surf%i(num_v)   = i
1553             surf%j(num_v)   = j
1554             surf%k(num_v)   = k
1555!
1556!--          Initialize surface-layer height, or more precisely, distance to surface
1557             IF ( north_facing  .OR.  south_facing )  THEN
1558                surf%z_mo(num_v)  = 0.5_wp * dy
1559             ELSE
1560                surf%z_mo(num_v)  = 0.5_wp * dx
1561             ENDIF
1562
1563             surf%facing(num_v)  = 0
1564!
1565!--          Surface orientation. Moreover, set component id to map wall_heatflux,
1566!--          etc., on surface type (further below)
1567             IF ( north_facing )  THEN
1568                surf%facing(num_v) = IBSET( surf%facing(num_v), 0 ) 
1569                component          = 4
1570             ENDIF
1571
1572             IF ( south_facing )  THEN
1573                surf%facing(num_v) = IBSET( surf%facing(num_v), 1 ) 
1574                component          = 3
1575             ENDIF
1576
1577             IF ( east_facing )  THEN
1578                surf%facing(num_v) = IBSET( surf%facing(num_v), 2 )
1579                component          = 2
1580             ENDIF
1581
1582             IF ( west_facing )  THEN
1583                surf%facing(num_v) = IBSET( surf%facing(num_v), 3 ) 
1584                component          = 1
1585             ENDIF
1586
1587 
1588             surf%z0(num_v)  = roughness_length
1589             surf%z0h(num_v) = z0h_factor * roughness_length
1590             surf%z0q(num_v) = z0h_factor * roughness_length
1591
1592             surf%us(num_v)  = 0.0_wp
1593!
1594!--          If required, initialize Obukhov length
1595             IF ( ALLOCATED( surf%ol ) )                                       &
1596                surf%ol(num_v) = surf%z_mo(num_v) / zeta_min
1597
1598             surf%uvw_abs(num_v)   = 0.0_wp
1599
1600             surf%mom_flux_uv(num_v) = 0.0_wp
1601             surf%mom_flux_w(num_v)  = 0.0_wp
1602             surf%mom_flux_tke(0:1,num_v) = 0.0_wp
1603
1604             surf%ts(num_v)    = 0.0_wp
1605             surf%shf(num_v)   = wall_heatflux(component)
1606
1607             IF ( humidity )  THEN
1608                surf%qs(num_v)   = 0.0_wp
1609                surf%qsws(num_v) = wall_humidityflux(component)
1610!
1611!--             Following wall fluxes are assumed to be zero
1612                IF ( cloud_physics .AND. microphysics_morrison)  THEN
1613                   surf%qcs(num_v) = 0.0_wp
1614                   surf%ncs(num_v) = 0.0_wp
1615   
1616                   surf%qcsws(num_v) = 0.0_wp
1617                   surf%ncsws(num_v) = 0.0_wp
1618                ENDIF
1619                IF ( cloud_physics .AND. microphysics_seifert)  THEN
1620                   surf%qrs(num_v) = 0.0_wp
1621                   surf%nrs(num_v) = 0.0_wp
1622   
1623                   surf%qrsws(num_v) = 0.0_wp
1624                   surf%nrsws(num_v) = 0.0_wp
1625                ENDIF
1626             ENDIF
1627
1628             IF ( passive_scalar )  THEN
1629                surf%ss(num_v)   = 0.0_wp
1630                surf%ssws(num_v) = wall_scalarflux(component)
1631             ENDIF
1632!
1633!--          So far, salinityflux at vertical surfaces is simply zero
1634!--          at the moment 
1635             IF ( ocean )  surf%sasws(num_v) = wall_salinityflux(component)
1636!
1637!--          Increment wall indices
1638             num_v                 = num_v + 1
1639             num_v_kji             = num_v_kji + 1
1640
1641          END SUBROUTINE initialize_vertical_surfaces
1642
1643    END SUBROUTINE init_surfaces
1644
1645!------------------------------------------------------------------------------!
1646! Description:
1647! ------------
1648!> Gathers all surface elements with the same facing (but possibly different
1649!> type) onto a surface type, and writes binary data into restart files.
1650!------------------------------------------------------------------------------!
1651    SUBROUTINE surface_write_restart_data
1652
1653       IMPLICIT NONE
1654
1655       CHARACTER(LEN=1)             ::  dum  !< dummy string to create output-variable name
1656
1657       INTEGER(iwp)                 ::  i    !< running index x-direction
1658       INTEGER(iwp)                 ::  j    !< running index y-direction
1659       INTEGER(iwp)                 ::  l    !< index surface type orientation
1660       INTEGER(iwp)                 ::  m    !< running index for surface elements on individual surface array
1661       INTEGER(iwp), DIMENSION(0:3) ::  mm   !< running index for surface elements on gathered surface array
1662
1663       TYPE(surf_type), DIMENSION(0:2) ::  surf_h !< gathered horizontal surfaces, contains all surface types
1664       TYPE(surf_type), DIMENSION(0:3) ::  surf_v !< gathered vertical surfaces, contains all surface types
1665
1666!
1667!--    Determine total number of horizontal and vertical surface elements before
1668!--    writing var_list
1669       CALL surface_last_actions
1670!
1671!--    Count number of grid points with same facing and allocate attributes respectively
1672!--    Horizontal upward facing
1673       surf_h(0)%ns = ns_h_on_file(0)
1674       CALL allocate_surface_attributes_h( surf_h(0), nys, nyn, nxl, nxr )
1675!
1676!--    Horizontal downward facing
1677       surf_h(1)%ns = ns_h_on_file(1)
1678       CALL allocate_surface_attributes_h( surf_h(1), nys, nyn, nxl, nxr )
1679!
1680!--    Model top
1681       surf_h(2)%ns = ns_h_on_file(2)
1682       CALL allocate_surface_attributes_h_top( surf_h(2), nys, nyn, nxl, nxr )
1683!
1684!--    Vertical surfaces
1685       DO  l = 0, 3
1686          surf_v(l)%ns = ns_v_on_file(l)
1687          CALL allocate_surface_attributes_v( surf_v(l), .FALSE.,              &
1688                                              nys, nyn, nxl, nxr )
1689       ENDDO
1690!
1691!--    In the following, gather data from surfaces elements with the same
1692!--    facing (but possibly differt type) on 1 data-type array.
1693       mm(0:2) = 1
1694       DO  l = 0, 2
1695          DO  i = nxl, nxr
1696             DO  j = nys, nyn
1697                DO  m = surf_def_h(l)%start_index(j,i),                        &
1698                        surf_def_h(l)%end_index(j,i)
1699                   IF ( ALLOCATED( surf_def_h(l)%us ) )                        &
1700                      surf_h(l)%us(mm(l))      = surf_def_h(l)%us(m)
1701                   IF ( ALLOCATED( surf_def_h(l)%ts ) )                        &
1702                      surf_h(l)%ts(mm(l))      = surf_def_h(l)%ts(m)
1703                   IF ( ALLOCATED( surf_def_h(l)%qs ) )                        &
1704                      surf_h(l)%qs(mm(l))      = surf_def_h(l)%qs(m)
1705                   IF ( ALLOCATED( surf_def_h(l)%ss ) )                        &
1706                      surf_h(l)%ss(mm(l))      = surf_def_h(l)%ss(m)
1707                   IF ( ALLOCATED( surf_def_h(l)%qcs ) )                       &
1708                      surf_h(l)%qcs(mm(l))     = surf_def_h(l)%qcs(m)
1709                   IF ( ALLOCATED( surf_def_h(l)%ncs ) )                       &
1710                      surf_h(l)%ncs(mm(l))     = surf_def_h(l)%ncs(m)
1711                   IF ( ALLOCATED( surf_def_h(l)%qrs ) )                       &
1712                      surf_h(l)%qrs(mm(l))     = surf_def_h(l)%qrs(m)
1713                   IF ( ALLOCATED( surf_def_h(l)%nrs ) )                       &
1714                      surf_h(l)%nrs(mm(l))     = surf_def_h(l)%nrs(m)
1715                   IF ( ALLOCATED( surf_def_h(l)%ol ) )                        &
1716                      surf_h(l)%ol(mm(l))      = surf_def_h(l)%ol(m)
1717                   IF ( ALLOCATED( surf_def_h(l)%rib ) )                       &
1718                      surf_h(l)%rib(mm(l))     = surf_def_h(l)%rib(m)
1719                   IF ( ALLOCATED( surf_def_h(l)%usws ) )                      &
1720                      surf_h(l)%usws(mm(l))    = surf_def_h(l)%usws(m)
1721                   IF ( ALLOCATED( surf_def_h(l)%vsws ) )                      &
1722                      surf_h(l)%vsws(mm(l))    = surf_def_h(l)%vsws(m)
1723                   IF ( ALLOCATED( surf_def_h(l)%shf ) )                       &
1724                      surf_h(l)%shf(mm(l))     = surf_def_h(l)%shf(m)
1725                   IF ( ALLOCATED( surf_def_h(l)%qsws ) )                      &
1726                      surf_h(l)%qsws(mm(l))    = surf_def_h(l)%qsws(m)
1727                   IF ( ALLOCATED( surf_def_h(l)%ssws ) )                      &
1728                      surf_h(l)%qsws(mm(l))    = surf_def_h(l)%ssws(m)
1729                   IF ( ALLOCATED( surf_def_h(l)%ncsws ) )                     &
1730                      surf_h(l)%ncsws(mm(l))   = surf_def_h(l)%ncsws(m)
1731                   IF ( ALLOCATED( surf_def_h(l)%nrsws ) )                     &
1732                      surf_h(l)%nrsws(mm(l))   = surf_def_h(l)%nrsws(m)
1733                   IF ( ALLOCATED( surf_def_h(l)%sasws ) )                     &
1734                      surf_h(l)%sasws(mm(l))   = surf_def_h(l)%sasws(m)
1735               
1736                   mm(l) = mm(l) + 1
1737                ENDDO
1738
1739                IF ( l == 0 )  THEN
1740                   DO  m = surf_lsm_h%start_index(j,i),                        &
1741                           surf_lsm_h%end_index(j,i)
1742                      IF ( ALLOCATED( surf_lsm_h%us ) )                        &
1743                         surf_h(0)%us(mm(0))      = surf_lsm_h%us(m)
1744                      IF ( ALLOCATED( surf_lsm_h%ts ) )                        &
1745                         surf_h(0)%ts(mm(0))      = surf_lsm_h%ts(m)
1746                      IF ( ALLOCATED( surf_lsm_h%qs ) )                        &
1747                         surf_h(0)%qs(mm(0))      = surf_lsm_h%qs(m)
1748                      IF ( ALLOCATED( surf_lsm_h%ss ) )                        &
1749                         surf_h(0)%ss(mm(0))      = surf_lsm_h%ss(m)
1750                      IF ( ALLOCATED( surf_lsm_h%qcs ) )                       &
1751                         surf_h(0)%qcs(mm(0))     = surf_lsm_h%qcs(m)
1752                      IF ( ALLOCATED( surf_lsm_h%ncs ) )                       &
1753                         surf_h(0)%ncs(mm(0))     = surf_lsm_h%ncs(m)
1754                      IF ( ALLOCATED( surf_lsm_h%qrs ) )                       &
1755                         surf_h(0)%qrs(mm(0))     = surf_lsm_h%qrs(m)
1756                      IF ( ALLOCATED( surf_lsm_h%nrs ) )                       &
1757                         surf_h(0)%nrs(mm(0))     = surf_lsm_h%nrs(m)
1758                      IF ( ALLOCATED( surf_lsm_h%ol ) )                        &
1759                         surf_h(0)%ol(mm(0))      = surf_lsm_h%ol(m)
1760                      IF ( ALLOCATED( surf_lsm_h%rib ) )                       &
1761                         surf_h(0)%rib(mm(0))     = surf_lsm_h%rib(m)
1762                      IF ( ALLOCATED( surf_lsm_h%usws ) )                      &
1763                         surf_h(0)%usws(mm(0))    = surf_lsm_h%usws(m)
1764                      IF ( ALLOCATED( surf_lsm_h%vsws ) )                      &
1765                         surf_h(0)%vsws(mm(0))    = surf_lsm_h%vsws(m)
1766                      IF ( ALLOCATED( surf_lsm_h%shf ) )                       &
1767                         surf_h(0)%shf(mm(0))     = surf_lsm_h%shf(m)
1768                      IF ( ALLOCATED( surf_lsm_h%qsws ) )                      &
1769                         surf_h(0)%qsws(mm(0))    = surf_lsm_h%qsws(m)
1770                      IF ( ALLOCATED( surf_lsm_h%ssws ) )                      &
1771                         surf_h(0)%qsws(mm(0))    = surf_lsm_h%ssws(m)
1772                      IF ( ALLOCATED( surf_lsm_h%ncsws ) )                     &
1773                         surf_h(0)%ncsws(mm(0))   = surf_lsm_h%ncsws(m)
1774                      IF ( ALLOCATED( surf_lsm_h%nrsws ) )                     &
1775                         surf_h(0)%nrsws(mm(0))   = surf_lsm_h%nrsws(m)
1776                      IF ( ALLOCATED( surf_lsm_h%sasws ) )                     &
1777                        surf_h(0)%sasws(mm(0))   = surf_lsm_h%sasws(m)
1778               
1779                      mm(0) = mm(0) + 1
1780             
1781                   ENDDO
1782
1783                   DO  m = surf_usm_h%start_index(j,i),                        &
1784                           surf_usm_h%end_index(j,i)
1785                      IF ( ALLOCATED( surf_usm_h%us ) )                        &
1786                         surf_h(0)%us(mm(0))      = surf_usm_h%us(m)
1787                      IF ( ALLOCATED( surf_usm_h%ts ) )                        &
1788                         surf_h(0)%ts(mm(0))      = surf_usm_h%ts(m)
1789                      IF ( ALLOCATED( surf_usm_h%qs ) )                        &
1790                         surf_h(0)%qs(mm(0))      = surf_usm_h%qs(m)
1791                      IF ( ALLOCATED( surf_usm_h%ss ) )                        &
1792                         surf_h(0)%ss(mm(0))      = surf_usm_h%ss(m)
1793                      IF ( ALLOCATED( surf_usm_h%qcs ) )                       &
1794                         surf_h(0)%qcs(mm(0))     = surf_usm_h%qcs(m)
1795                      IF ( ALLOCATED( surf_usm_h%ncs ) )                       &
1796                         surf_h(0)%ncs(mm(0))     = surf_usm_h%ncs(m)
1797                      IF ( ALLOCATED( surf_usm_h%qrs ) )                       &
1798                         surf_h(0)%qrs(mm(0))     = surf_usm_h%qrs(m)
1799                      IF ( ALLOCATED( surf_usm_h%nrs ) )                       &
1800                         surf_h(0)%nrs(mm(0))     = surf_usm_h%nrs(m)
1801                      IF ( ALLOCATED( surf_usm_h%ol ) )                        &
1802                         surf_h(0)%ol(mm(0))      = surf_usm_h%ol(m)
1803                      IF ( ALLOCATED( surf_usm_h%rib ) )                       &
1804                         surf_h(0)%rib(mm(0))     = surf_usm_h%rib(m)
1805                      IF ( ALLOCATED( surf_usm_h%usws ) )                      &
1806                         surf_h(0)%usws(mm(0))    = surf_usm_h%usws(m)
1807                      IF ( ALLOCATED( surf_usm_h%vsws ) )                      &
1808                         surf_h(0)%vsws(mm(0))    = surf_usm_h%vsws(m)
1809                      IF ( ALLOCATED( surf_usm_h%shf ) )                       &
1810                         surf_h(0)%shf(mm(0))     = surf_usm_h%shf(m)
1811                      IF ( ALLOCATED( surf_usm_h%qsws ) )                      &
1812                         surf_h(0)%qsws(mm(0))    = surf_usm_h%qsws(m)
1813                      IF ( ALLOCATED( surf_usm_h%ssws ) )                      &
1814                         surf_h(0)%qsws(mm(0))    = surf_usm_h%ssws(m)
1815                      IF ( ALLOCATED( surf_usm_h%ncsws ) )                     &
1816                         surf_h(0)%ncsws(mm(0))   = surf_usm_h%ncsws(m)
1817                      IF ( ALLOCATED( surf_usm_h%nrsws ) )                     &
1818                         surf_h(0)%nrsws(mm(0))   = surf_usm_h%nrsws(m)
1819                      IF ( ALLOCATED( surf_usm_h%sasws ) )                     &
1820                        surf_h(0)%sasws(mm(0))   = surf_usm_h%sasws(m)
1821               
1822                      mm(0) = mm(0) + 1
1823             
1824                   ENDDO
1825
1826
1827                ENDIF
1828
1829             ENDDO
1830
1831          ENDDO
1832          IF ( l == 0 )  THEN
1833             surf_h(l)%start_index = MAX( surf_def_h(l)%start_index,           &
1834                                          surf_lsm_h%start_index,              &
1835                                          surf_usm_h%start_index )
1836             surf_h(l)%end_index   = MAX( surf_def_h(l)%end_index,             &
1837                                          surf_lsm_h%end_index,                &
1838                                          surf_usm_h%end_index )
1839          ELSE
1840             surf_h(l)%start_index = surf_def_h(l)%start_index
1841             surf_h(l)%end_index   = surf_def_h(l)%end_index
1842          ENDIF
1843       ENDDO
1844
1845
1846       mm(0:3) = 1
1847       DO  l = 0, 3
1848          DO  i = nxl, nxr
1849             DO  j = nys, nyn
1850                DO  m = surf_def_v(l)%start_index(j,i),                        &
1851                        surf_def_v(l)%end_index(j,i)
1852                   IF ( ALLOCATED( surf_def_v(l)%us ) )                        &
1853                      surf_v(l)%us(mm(l))      = surf_def_v(l)%us(m)
1854                   IF ( ALLOCATED( surf_def_v(l)%ts ) )                        &
1855                      surf_v(l)%ts(mm(l))      = surf_def_v(l)%ts(m)
1856                   IF ( ALLOCATED( surf_def_v(l)%qs ) )                        &
1857                      surf_v(l)%qs(mm(l))      = surf_def_v(l)%qs(m)
1858                   IF ( ALLOCATED( surf_def_v(l)%ss ) )                        &
1859                      surf_v(l)%ss(mm(l))      = surf_def_v(l)%ss(m)
1860                   IF ( ALLOCATED( surf_def_v(l)%qcs ) )                       &
1861                      surf_v(l)%qcs(mm(l))     = surf_def_v(l)%qcs(m)
1862                   IF ( ALLOCATED( surf_def_v(l)%ncs ) )                       &
1863                      surf_v(l)%ncs(mm(l))     = surf_def_v(l)%ncs(m)
1864                   IF ( ALLOCATED( surf_def_v(l)%qrs ) )                       &
1865                      surf_v(l)%qrs(mm(l))     = surf_def_v(l)%qrs(m)
1866                   IF ( ALLOCATED( surf_def_v(l)%nrs ) )                       &
1867                      surf_v(l)%nrs(mm(l))     = surf_def_v(l)%nrs(m)
1868                   IF ( ALLOCATED( surf_def_v(l)%ol ) )                        &
1869                      surf_v(l)%ol(mm(l))      = surf_def_v(l)%ol(m)
1870                   IF ( ALLOCATED( surf_def_v(l)%rib ) )                       &
1871                      surf_v(l)%rib(mm(l))     = surf_def_v(l)%rib(m)
1872                   IF ( ALLOCATED( surf_def_v(l)%shf ) )                       &
1873                      surf_v(l)%shf(mm(l))     = surf_def_v(l)%shf(m)
1874                   IF ( ALLOCATED( surf_def_v(l)%qsws ) )                      &
1875                      surf_v(l)%qsws(mm(l))    = surf_def_v(l)%qsws(m)
1876                   IF ( ALLOCATED( surf_def_v(l)%ssws ) )                      &
1877                      surf_v(l)%qsws(mm(l))    = surf_def_v(l)%ssws(m)
1878                   IF ( ALLOCATED( surf_def_v(l)%ncsws ) )                     &
1879                      surf_v(l)%ncsws(mm(l))   = surf_def_v(l)%ncsws(m)
1880                   IF ( ALLOCATED( surf_def_v(l)%nrsws ) )                     &
1881                      surf_v(l)%nrsws(mm(l))   = surf_def_v(l)%nrsws(m)
1882                   IF ( ALLOCATED( surf_def_v(l)%sasws ) )                     &
1883                      surf_v(l)%sasws(mm(l))   = surf_def_v(l)%sasws(m)
1884                   IF ( ALLOCATED( surf_def_v(l)%mom_flux_uv) )                &
1885                      surf_v(l)%mom_flux_uv(mm(l))  = surf_def_v(l)%mom_flux_uv(m)
1886                   IF ( ALLOCATED( surf_def_v(l)%mom_flux_w) )                 &
1887                      surf_v(l)%mom_flux_w(mm(l))   = surf_def_v(l)%mom_flux_w(m)
1888                   IF ( ALLOCATED( surf_def_v(l)%mom_flux_tke) )               &
1889                      surf_v(l)%mom_flux_tke(0:1,mm(l)) = surf_def_v(l)%mom_flux_tke(0:1,m)
1890               
1891                   mm(l) = mm(l) + 1
1892                ENDDO
1893
1894                DO  m = surf_lsm_v(l)%start_index(j,i),                        &
1895                        surf_lsm_v(l)%end_index(j,i)
1896                   IF ( ALLOCATED( surf_lsm_v(l)%us ) )                        &
1897                      surf_v(l)%us(mm(l))      = surf_lsm_v(l)%us(m)
1898                   IF ( ALLOCATED( surf_lsm_v(l)%ts ) )                        &
1899                      surf_v(l)%ts(mm(l))      = surf_lsm_v(l)%ts(m)
1900                   IF ( ALLOCATED( surf_lsm_v(l)%qs ) )                        &
1901                      surf_v(l)%qs(mm(l))      = surf_lsm_v(l)%qs(m)
1902                   IF ( ALLOCATED( surf_lsm_v(l)%ss ) )                        &
1903                      surf_v(l)%ss(mm(l))      = surf_lsm_v(l)%ss(m)
1904                   IF ( ALLOCATED( surf_lsm_v(l)%qcs ) )                       &
1905                      surf_v(l)%qcs(mm(l))     = surf_lsm_v(l)%qcs(m)
1906                   IF ( ALLOCATED( surf_lsm_v(l)%ncs ) )                       &
1907                      surf_v(l)%ncs(mm(l))     = surf_lsm_v(l)%ncs(m)
1908                   IF ( ALLOCATED( surf_lsm_v(l)%qrs ) )                       &
1909                      surf_v(l)%qrs(mm(l))     = surf_lsm_v(l)%qrs(m)
1910                   IF ( ALLOCATED( surf_lsm_v(l)%nrs ) )                       &
1911                      surf_v(l)%nrs(mm(l))     = surf_lsm_v(l)%nrs(m)
1912                   IF ( ALLOCATED( surf_lsm_v(l)%ol ) )                        &
1913                      surf_v(l)%ol(mm(l))      = surf_lsm_v(l)%ol(m)
1914                   IF ( ALLOCATED( surf_lsm_v(l)%rib ) )                       &
1915                      surf_v(l)%rib(mm(l))     = surf_lsm_v(l)%rib(m)
1916                   IF ( ALLOCATED( surf_lsm_v(l)%usws ) )                      &
1917                      surf_v(l)%usws(mm(l))    = surf_lsm_v(l)%usws(m)
1918                   IF ( ALLOCATED( surf_lsm_v(l)%vsws ) )                      &
1919                      surf_v(l)%vsws(mm(l))    = surf_lsm_v(l)%vsws(m)
1920                   IF ( ALLOCATED( surf_lsm_v(l)%shf ) )                       &
1921                      surf_v(l)%shf(mm(l))     = surf_lsm_v(l)%shf(m)
1922                   IF ( ALLOCATED( surf_lsm_v(l)%qsws ) )                      &
1923                      surf_v(l)%qsws(mm(l))    = surf_lsm_v(l)%qsws(m)
1924                   IF ( ALLOCATED( surf_lsm_v(l)%ssws ) )                      &
1925                      surf_v(l)%qsws(mm(l))    = surf_lsm_v(l)%ssws(m)
1926                   IF ( ALLOCATED( surf_lsm_v(l)%ncsws ) )                     &
1927                      surf_v(l)%ncsws(mm(l))   = surf_lsm_v(l)%ncsws(m)
1928                   IF ( ALLOCATED( surf_lsm_v(l)%nrsws ) )                     &
1929                      surf_v(l)%nrsws(mm(l))   = surf_lsm_v(l)%nrsws(m)
1930                   IF ( ALLOCATED( surf_lsm_v(l)%sasws ) )                     &
1931                      surf_v(l)%sasws(mm(l))   = surf_lsm_v(l)%sasws(m)
1932                   IF ( ALLOCATED( surf_lsm_v(l)%mom_flux_uv) )                &
1933                      surf_v(l)%mom_flux_uv(mm(l))  = surf_lsm_v(l)%mom_flux_uv(m)
1934                   IF ( ALLOCATED( surf_lsm_v(l)%mom_flux_w) )                 &
1935                      surf_v(l)%mom_flux_w(mm(l))   = surf_lsm_v(l)%mom_flux_w(m)
1936                   IF ( ALLOCATED( surf_lsm_v(l)%mom_flux_tke) )               &
1937                      surf_v(l)%mom_flux_tke(0:1,mm(l)) = surf_lsm_v(l)%mom_flux_tke(0:1,m)
1938               
1939                   mm(l) = mm(l) + 1
1940                ENDDO
1941
1942                DO  m = surf_usm_v(l)%start_index(j,i),                        &
1943                        surf_usm_v(l)%end_index(j,i)
1944                   IF ( ALLOCATED( surf_usm_v(l)%us ) )                        &
1945                      surf_v(l)%us(mm(l))      = surf_usm_v(l)%us(m)
1946                   IF ( ALLOCATED( surf_usm_v(l)%ts ) )                        &
1947                      surf_v(l)%ts(mm(l))      = surf_usm_v(l)%ts(m)
1948                   IF ( ALLOCATED( surf_usm_v(l)%qs ) )                        &
1949                      surf_v(l)%qs(mm(l))      = surf_usm_v(l)%qs(m)
1950                   IF ( ALLOCATED( surf_usm_v(l)%ss ) )                        &
1951                      surf_v(l)%ss(mm(l))      = surf_usm_v(l)%ss(m)
1952                   IF ( ALLOCATED( surf_usm_v(l)%qcs ) )                       &
1953                      surf_v(l)%qcs(mm(l))     = surf_usm_v(l)%qcs(m)
1954                   IF ( ALLOCATED( surf_usm_v(l)%ncs ) )                       &
1955                      surf_v(l)%ncs(mm(l))     = surf_usm_v(l)%ncs(m)
1956                   IF ( ALLOCATED( surf_usm_v(l)%qrs ) )                       &
1957                      surf_v(l)%qrs(mm(l))     = surf_usm_v(l)%qrs(m)
1958                   IF ( ALLOCATED( surf_usm_v(l)%nrs ) )                       &
1959                      surf_v(l)%nrs(mm(l))     = surf_usm_v(l)%nrs(m)
1960                   IF ( ALLOCATED( surf_usm_v(l)%ol ) )                        &
1961                      surf_v(l)%ol(mm(l))      = surf_usm_v(l)%ol(m)
1962                   IF ( ALLOCATED( surf_usm_v(l)%rib ) )                       &
1963                      surf_v(l)%rib(mm(l))     = surf_usm_v(l)%rib(m)
1964                   IF ( ALLOCATED( surf_usm_v(l)%usws ) )                      &
1965                      surf_v(l)%usws(mm(l))    = surf_usm_v(l)%usws(m)
1966                   IF ( ALLOCATED( surf_usm_v(l)%vsws ) )                      &
1967                      surf_v(l)%vsws(mm(l))    = surf_usm_v(l)%vsws(m)
1968                   IF ( ALLOCATED( surf_usm_v(l)%shf ) )                       &
1969                      surf_v(l)%shf(mm(l))     = surf_usm_v(l)%shf(m)
1970                   IF ( ALLOCATED( surf_usm_v(l)%qsws ) )                      &
1971                      surf_v(l)%qsws(mm(l))    = surf_usm_v(l)%qsws(m)
1972                   IF ( ALLOCATED( surf_usm_v(l)%ssws ) )                      &
1973                      surf_v(l)%qsws(mm(l))    = surf_usm_v(l)%ssws(m)
1974                   IF ( ALLOCATED( surf_usm_v(l)%ncsws ) )                     &
1975                      surf_v(l)%ncsws(mm(l))   = surf_usm_v(l)%ncsws(m)
1976                   IF ( ALLOCATED( surf_usm_v(l)%nrsws ) )                     &
1977                      surf_v(l)%nrsws(mm(l))   = surf_usm_v(l)%nrsws(m)
1978                   IF ( ALLOCATED( surf_usm_v(l)%sasws ) )                     &
1979                      surf_v(l)%sasws(mm(l))   = surf_usm_v(l)%sasws(m)
1980                   IF ( ALLOCATED( surf_usm_v(l)%mom_flux_uv) )                &
1981                      surf_v(l)%mom_flux_uv(mm(l))  = surf_usm_v(l)%mom_flux_uv(m)
1982                   IF ( ALLOCATED( surf_usm_v(l)%mom_flux_w) )                 &
1983                      surf_v(l)%mom_flux_w(mm(l))   = surf_usm_v(l)%mom_flux_w(m)
1984                   IF ( ALLOCATED( surf_usm_v(l)%mom_flux_tke) )               &
1985                      surf_v(l)%mom_flux_tke(0:1,mm(l)) = surf_usm_v(l)%mom_flux_tke(0:1,m)
1986               
1987                   mm(l) = mm(l) + 1
1988                ENDDO
1989             
1990             ENDDO
1991          ENDDO
1992!
1993!--       Finally, determine start- and end-index for the respective surface
1994          surf_v(l)%start_index = MAX( surf_def_v(l)%start_index,              &
1995                                       surf_lsm_v(l)%start_index,              &
1996                                       surf_usm_v(l)%start_index )
1997          surf_v(l)%end_index   = MAX( surf_def_v(l)%end_index,                &
1998                                       surf_lsm_v(l)%end_index,                &
1999                                       surf_usm_v(l)%end_index   )
2000       ENDDO
2001
2002       WRITE ( 14 )  'ns_h_on_file                  '
2003       WRITE ( 14 )   ns_h_on_file
2004       WRITE ( 14 )  'ns_v_on_file                  '
2005       WRITE ( 14 )   ns_v_on_file
2006!
2007!--    Write required restart data.
2008!--    Start with horizontal surfaces (upward-, downward-facing, and model top)
2009       DO  l = 0, 2
2010          WRITE( dum, '(I1)')  l
2011         
2012          WRITE ( 14 )  'surf_h(' // dum // ')%start_index         ' 
2013          WRITE ( 14 )   surf_h(l)%start_index
2014          WRITE ( 14 )  'surf_h(' // dum // ')%end_index           ' 
2015          WRITE ( 14 )   surf_h(l)%end_index
2016
2017          WRITE ( 14 )  'surf_h(' // dum // ')%us                  ' 
2018          IF ( ALLOCATED ( surf_h(l)%us ) )  THEN
2019             WRITE ( 14 )  surf_h(l)%us
2020          ENDIF
2021          WRITE ( 14 )  'surf_h(' // dum // ')%ts                  ' 
2022          IF ( ALLOCATED ( surf_h(l)%ts ) )  THEN
2023             WRITE ( 14 )  surf_h(l)%ts
2024          ENDIF
2025          WRITE ( 14 )  'surf_h(' // dum // ')%qs                  ' 
2026          IF ( ALLOCATED ( surf_h(l)%qs ) )  THEN
2027             WRITE ( 14 )  surf_h(l)%qs
2028          ENDIF
2029          WRITE ( 14 )  'surf_h(' // dum // ')%ss                  ' 
2030          IF ( ALLOCATED ( surf_h(l)%ss ) )  THEN
2031             WRITE ( 14 )  surf_h(l)%ss
2032          ENDIF
2033          WRITE ( 14 )  'surf_h(' // dum // ')%qcs                 '
2034          IF ( ALLOCATED ( surf_h(l)%qcs ) )  THEN 
2035             WRITE ( 14 )  surf_h(l)%qcs
2036          ENDIF
2037          WRITE ( 14 )  'surf_h(' // dum // ')%ncs                 ' 
2038          IF ( ALLOCATED ( surf_h(l)%ncs ) )  THEN
2039             WRITE ( 14 )  surf_h(l)%ncs
2040          ENDIF
2041          WRITE ( 14 )  'surf_h(' // dum // ')%qrs                 '
2042          IF ( ALLOCATED ( surf_h(l)%qrs ) )  THEN 
2043             WRITE ( 14 )  surf_h(l)%qrs
2044          ENDIF
2045          WRITE ( 14 )  'surf_h(' // dum // ')%nrs                 ' 
2046          IF ( ALLOCATED ( surf_h(l)%nrs ) )  THEN
2047             WRITE ( 14 )  surf_h(l)%nrs
2048          ENDIF
2049          WRITE ( 14 )  'surf_h(' // dum // ')%ol                  ' 
2050          IF ( ALLOCATED ( surf_h(l)%ol ) )  THEN
2051             WRITE ( 14 )  surf_h(l)%ol
2052          ENDIF
2053          WRITE ( 14 )  'surf_h(' // dum // ')%rib                 ' 
2054          IF ( ALLOCATED ( surf_h(l)%rib ) )  THEN
2055             WRITE ( 14 )  surf_h(l)%rib
2056          ENDIF
2057          WRITE ( 14 )  'surf_h(' // dum // ')%usws                ' 
2058          IF ( ALLOCATED ( surf_h(l)%usws ) )  THEN
2059             WRITE ( 14 )  surf_h(l)%usws
2060          ENDIF
2061          WRITE ( 14 )  'surf_h(' // dum // ')%vsws                ' 
2062          IF ( ALLOCATED ( surf_h(l)%vsws ) )  THEN
2063             WRITE ( 14 )  surf_h(l)%vsws
2064          ENDIF
2065          WRITE ( 14 )  'surf_h(' // dum // ')%shf                 ' 
2066          IF ( ALLOCATED ( surf_h(l)%shf ) )  THEN
2067             WRITE ( 14 )  surf_h(l)%shf
2068          ENDIF
2069          WRITE ( 14 )  'surf_h(' // dum // ')%qsws                ' 
2070          IF ( ALLOCATED ( surf_h(l)%qsws ) )  THEN
2071             WRITE ( 14 )  surf_h(l)%qsws
2072          ENDIF
2073          WRITE ( 14 )  'surf_h(' // dum // ')%ssws                ' 
2074          IF ( ALLOCATED ( surf_h(l)%ssws ) )  THEN
2075             WRITE ( 14 )  surf_h(l)%ssws
2076          ENDIF
2077          WRITE ( 14 )  'surf_h(' // dum // ')%qcsws               ' 
2078          IF ( ALLOCATED ( surf_h(l)%qcsws ) )  THEN
2079             WRITE ( 14 )  surf_h(l)%qcsws
2080          ENDIF
2081          WRITE ( 14 )  'surf_h(' // dum // ')%ncsws               ' 
2082          IF ( ALLOCATED ( surf_h(l)%ncsws ) )  THEN
2083             WRITE ( 14 )  surf_h(l)%ncsws
2084          ENDIF
2085          WRITE ( 14 )  'surf_h(' // dum // ')%qrsws               ' 
2086          IF ( ALLOCATED ( surf_h(l)%qrsws ) )  THEN
2087             WRITE ( 14 )  surf_h(l)%qrsws
2088          ENDIF
2089          WRITE ( 14 )  'surf_h(' // dum // ')%nrsws               ' 
2090          IF ( ALLOCATED ( surf_h(l)%nrsws ) )  THEN
2091             WRITE ( 14 )  surf_h(l)%nrsws
2092          ENDIF
2093          WRITE ( 14 )  'surf_h(' // dum // ')%sasws               ' 
2094          IF ( ALLOCATED ( surf_h(l)%sasws ) )  THEN
2095             WRITE ( 14 )  surf_h(l)%sasws
2096          ENDIF
2097       ENDDO
2098!
2099!--    Write vertical surfaces
2100       DO  l = 0, 3
2101          WRITE( dum, '(I1)')  l
2102
2103          WRITE ( 14 )  'surf_v(' // dum // ')%start_index         ' 
2104          WRITE ( 14 )   surf_v(l)%start_index
2105          WRITE ( 14 )  'surf_v(' // dum // ')%end_index           ' 
2106          WRITE ( 14 )   surf_v(l)%end_index
2107
2108          WRITE ( 14 )  'surf_v(' // dum // ')%us                  ' 
2109          IF ( ALLOCATED ( surf_v(l)%us ) )  THEN
2110             WRITE ( 14 )  surf_v(l)%us
2111          ENDIF
2112          WRITE ( 14 )  'surf_v(' // dum // ')%ts                  ' 
2113          IF ( ALLOCATED ( surf_v(l)%ts ) )  THEN
2114             WRITE ( 14 )  surf_v(l)%ts
2115          ENDIF
2116          WRITE ( 14 )  'surf_v(' // dum // ')%qs                  ' 
2117          IF ( ALLOCATED ( surf_v(l)%qs ) )  THEN
2118             WRITE ( 14 )  surf_v(l)%qs
2119          ENDIF
2120          WRITE ( 14 )  'surf_v(' // dum // ')%ss                  ' 
2121          IF ( ALLOCATED ( surf_v(l)%ss ) )  THEN
2122             WRITE ( 14 )  surf_v(l)%ss
2123          ENDIF
2124          WRITE ( 14 )  'surf_v(' // dum // ')%qcs                 ' 
2125          IF ( ALLOCATED ( surf_v(l)%qcs ) )  THEN
2126             WRITE ( 14 )  surf_v(l)%qcs
2127          ENDIF
2128          WRITE ( 14 )  'surf_v(' // dum // ')%ncs                 ' 
2129          IF ( ALLOCATED ( surf_v(l)%ncs ) )  THEN
2130             WRITE ( 14 )  surf_v(l)%ncs
2131          ENDIF
2132          WRITE ( 14 )  'surf_v(' // dum // ')%qrs                 ' 
2133          IF ( ALLOCATED ( surf_v(l)%qrs ) )  THEN
2134             WRITE ( 14 )  surf_v(l)%qrs
2135          ENDIF
2136          WRITE ( 14 )  'surf_v(' // dum // ')%nrs                 ' 
2137          IF ( ALLOCATED ( surf_v(l)%nrs ) )  THEN
2138             WRITE ( 14 )  surf_v(l)%nrs
2139          ENDIF
2140          WRITE ( 14 )  'surf_v(' // dum // ')%ol                  ' 
2141          IF ( ALLOCATED ( surf_v(l)%ol ) )  THEN
2142             WRITE ( 14 )  surf_v(l)%ol
2143          ENDIF
2144          WRITE ( 14 )  'surf_v(' // dum // ')%rib                 ' 
2145          IF ( ALLOCATED ( surf_v(l)%rib ) )  THEN
2146             WRITE ( 14 )  surf_v(l)%rib
2147          ENDIF
2148          WRITE ( 14 )  'surf_v(' // dum // ')%shf                 ' 
2149          IF ( ALLOCATED ( surf_v(l)%shf ) )  THEN
2150             WRITE ( 14 )  surf_v(l)%shf
2151          ENDIF
2152          WRITE ( 14 )  'surf_v(' // dum // ')%qsws                ' 
2153          IF ( ALLOCATED ( surf_v(l)%qsws ) )  THEN
2154             WRITE ( 14 )  surf_v(l)%qsws
2155          ENDIF
2156          WRITE ( 14 )  'surf_v(' // dum // ')%ssws                ' 
2157          IF ( ALLOCATED ( surf_v(l)%ssws ) )  THEN
2158             WRITE ( 14 )  surf_v(l)%ssws
2159          ENDIF
2160          WRITE ( 14 )  'surf_v(' // dum // ')%qcsws               ' 
2161          IF ( ALLOCATED ( surf_v(l)%qcsws ) )  THEN
2162             WRITE ( 14 )  surf_v(l)%qcsws
2163          ENDIF
2164          WRITE ( 14 )  'surf_v(' // dum // ')%ncsws               ' 
2165          IF ( ALLOCATED ( surf_v(l)%ncsws ) )  THEN
2166             WRITE ( 14 )  surf_v(l)%ncsws
2167          ENDIF
2168          WRITE ( 14 )  'surf_v(' // dum // ')%qrsws               ' 
2169          IF ( ALLOCATED ( surf_v(l)%qrsws ) )  THEN
2170             WRITE ( 14 )  surf_v(l)%qrsws
2171          ENDIF
2172          WRITE ( 14 )  'surf_v(' // dum // ')%nrsws               ' 
2173          IF ( ALLOCATED ( surf_v(l)%nrsws ) )  THEN
2174             WRITE ( 14 )  surf_v(l)%nrsws
2175          ENDIF
2176          WRITE ( 14 )  'surf_v(' // dum // ')%sasws               ' 
2177          IF ( ALLOCATED ( surf_v(l)%sasws ) )  THEN
2178             WRITE ( 14 )  surf_v(l)%sasws
2179          ENDIF
2180          WRITE ( 14 )  'surf_v(' // dum // ')%mom_uv              ' 
2181          IF ( ALLOCATED ( surf_v(l)%mom_flux_uv ) )  THEN
2182             WRITE ( 14 )  surf_v(l)%mom_flux_uv
2183          ENDIF
2184          WRITE ( 14 )  'surf_v(' // dum // ')%mom_w               ' 
2185          IF ( ALLOCATED ( surf_v(l)%mom_flux_w ) )  THEN
2186             WRITE ( 14 )  surf_v(l)%mom_flux_w
2187          ENDIF
2188          WRITE ( 14 )  'surf_v(' // dum // ')%mom_tke             ' 
2189          IF ( ALLOCATED ( surf_v(l)%mom_flux_tke ) )  THEN
2190             WRITE ( 14 )  surf_v(l)%mom_flux_tke
2191          ENDIF
2192
2193       ENDDO
2194
2195       WRITE ( 14 )  '*** end surf ***              '
2196
2197    END SUBROUTINE surface_write_restart_data
2198
2199
2200!------------------------------------------------------------------------------!
2201! Description:
2202! ------------
2203!> Reads surface-related restart data. Please note, restart data for a certain
2204!> surface orientation (e.g. horizontal upward-facing) is stored in one
2205!> array, even if surface elements may belong to different surface types
2206!> natural or urban for example). Surface elements are redistributed into its
2207!> respective surface types within this routine. This allows e.g. changing the
2208!> surface type after reading the restart data, which might be required in case
2209!> of cyclic_fill mode.
2210!------------------------------------------------------------------------------!
2211    SUBROUTINE surface_read_restart_data( ii,                                  &
2212                                       nxlfa, nxl_on_file, nxrfa, nxr_on_file, &
2213                                       nynfa, nyn_on_file, nysfa, nys_on_file, &
2214                                       offset_xa, offset_ya, overlap_count )
2215
2216       USE pegrid,                                                             &
2217           ONLY: numprocs_previous_run
2218
2219       CHARACTER (LEN=1)  ::  dum         !< dummy to create correct string for reading input variable
2220       CHARACTER (LEN=30) ::  field_chr   !< input variable
2221
2222       INTEGER(iwp)       ::  i           !< running index along x-direction, refers to former domain size
2223       INTEGER(iwp)       ::  ic          !< running index along x-direction, refers to current domain size
2224       INTEGER(iwp)       ::  j           !< running index along y-direction, refers to former domain size
2225       INTEGER(iwp)       ::  jc          !< running index along y-direction, refers to former domain size
2226       INTEGER(iwp)       ::  k           !< running index along z-direction
2227       INTEGER(iwp)       ::  l           !< index variable for surface type
2228       INTEGER(iwp)       ::  m           !< running index for surface elements, refers to gathered array encompassing all surface types
2229       INTEGER(iwp)       ::  mm          !< running index for surface elements, refers to individual surface types
2230
2231       INTEGER(iwp)       ::  ii               !< running index over input files
2232       INTEGER(iwp)       ::  kk               !< running index over previous input files covering current local domain
2233       INTEGER(iwp)       ::  nxlc             !< index of left boundary on current subdomain
2234       INTEGER(iwp)       ::  nxlf             !< index of left boundary on former subdomain
2235       INTEGER(iwp)       ::  nxl_on_file      !< index of left boundary on former local domain
2236       INTEGER(iwp)       ::  nxrc             !< index of right boundary on current subdomain
2237       INTEGER(iwp)       ::  nxrf             !< index of right boundary on former subdomain
2238       INTEGER(iwp)       ::  nxr_on_file      !< index of right boundary on former local domain 
2239       INTEGER(iwp)       ::  nync             !< index of north boundary on current subdomain
2240       INTEGER(iwp)       ::  nynf             !< index of north boundary on former subdomain
2241       INTEGER(iwp)       ::  nyn_on_file      !< index of norht boundary on former local domain 
2242       INTEGER(iwp)       ::  nysc             !< index of south boundary on current subdomain
2243       INTEGER(iwp)       ::  nysf             !< index of south boundary on former subdomain
2244       INTEGER(iwp)       ::  nys_on_file      !< index of south boundary on former local domain 
2245       INTEGER(iwp)       ::  overlap_count    !< number of overlaps
2246 
2247       INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxlfa       !<
2248       INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxrfa       !<
2249       INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nynfa       !<
2250       INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nysfa       !<
2251       INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_xa   !<
2252       INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_ya   !<
2253
2254
2255       LOGICAL                         ::  horizontal_surface !< flag indicating horizontal surfaces
2256       LOGICAL                         ::  surf_match_def     !< flag indicating that surface element is of default type
2257       LOGICAL                         ::  surf_match_lsm     !< flag indicating that surface element is of natural type
2258       LOGICAL                         ::  surf_match_usm     !< flag indicating that surface element is of urban type
2259       LOGICAL                         ::  vertical_surface   !< flag indicating vertical surfaces
2260
2261       TYPE(surf_type), DIMENSION(0:2) ::  surf_h             !< horizontal surface type on file
2262       TYPE(surf_type), DIMENSION(0:3) ::  surf_v             !< vertical surface type on file
2263
2264!
2265!--    Read number of respective surface elements on file
2266       READ ( 13 )  field_chr
2267       IF ( TRIM( field_chr ) /= 'ns_h_on_file' )  THEN
2268!
2269!--       Add a proper error message
2270       ENDIF
2271       READ ( 13 ) ns_h_on_file
2272
2273       READ ( 13 )  field_chr
2274       IF ( TRIM( field_chr ) /= 'ns_v_on_file' )  THEN
2275!
2276!--       Add a proper error message
2277       ENDIF
2278       READ ( 13 ) ns_v_on_file
2279!
2280!--    Allocate memory for number of surface elements on file. Please note,
2281!--    these number is not necessarily the same as the final number of surface
2282!--    elements on local domain, which is the case if processor topology changes
2283!--    during restart runs.
2284!--    Horizontal upward facing
2285       surf_h(0)%ns = ns_h_on_file(0)
2286       CALL allocate_surface_attributes_h( surf_h(0),                          &
2287                                           nys_on_file, nyn_on_file,           &
2288                                           nxl_on_file, nxr_on_file )
2289!
2290!--    Horizontal downward facing
2291       surf_h(1)%ns = ns_h_on_file(1)
2292       CALL allocate_surface_attributes_h( surf_h(1),                          &
2293                                           nys_on_file, nyn_on_file,           &
2294                                           nxl_on_file, nxr_on_file )
2295!
2296!--    Model top
2297       surf_h(2)%ns = ns_h_on_file(2)
2298       CALL allocate_surface_attributes_h_top( surf_h(2),                      &
2299                                               nys_on_file, nyn_on_file,       &
2300                                               nxl_on_file, nxr_on_file )
2301!
2302!--    Vertical surfaces
2303       DO  l = 0, 3
2304          surf_v(l)%ns = ns_v_on_file(l)
2305          CALL allocate_surface_attributes_v( surf_v(l), .FALSE.,              &
2306                                              nys_on_file, nyn_on_file,        &
2307                                              nxl_on_file, nxr_on_file )
2308       ENDDO
2309
2310       IF ( initializing_actions == 'read_restart_data'  .OR.                  &
2311            initializing_actions == 'cyclic_fill' )  THEN
2312!
2313!--       Initial setting of flags for horizontal and vertical surfaces, will
2314!--       be set after start- and end-indices are read.
2315          horizontal_surface = .FALSE.
2316          vertical_surface   = .FALSE.
2317
2318          READ ( 13 )  field_chr
2319
2320          DO  WHILE ( TRIM( field_chr ) /= '*** end surf ***' )
2321!
2322!--          Map data on file as often as needed (data are read only for k=1)
2323             DO  kk = 1, overlap_count
2324!
2325!--             Get the index range of the subdomain on file which overlap with the
2326!--             current subdomain
2327                nxlf = nxlfa(ii,kk)
2328                nxlc = nxlfa(ii,kk) + offset_xa(ii,kk)
2329                nxrf = nxrfa(ii,kk)
2330                nxrc = nxrfa(ii,kk) + offset_xa(ii,kk)
2331                nysf = nysfa(ii,kk)
2332                nysc = nysfa(ii,kk) + offset_ya(ii,kk)
2333                nynf = nynfa(ii,kk)
2334                nync = nynfa(ii,kk) + offset_ya(ii,kk)
2335
2336                SELECT CASE ( TRIM( field_chr ) )
2337
2338                   CASE ( 'surf_h(0)%start_index' )
2339                      IF ( kk == 1 )                                           &
2340                         READ ( 13 )  surf_h(0)%start_index
2341                      l = 0
2342                   CASE ( 'surf_h(0)%end_index' )   
2343                      IF ( kk == 1 )                                           &
2344                         READ ( 13 )  surf_h(0)%end_index
2345                      horizontal_surface = .TRUE.
2346                      vertical_surface   = .FALSE.
2347                   CASE ( 'surf_h(0)%us' )         
2348                      IF ( ALLOCATED( surf_h(0)%us )  .AND.  kk == 1 )         &
2349                         READ ( 13 )  surf_h(0)%us
2350                   CASE ( 'surf_h(0)%ts' )         
2351                      IF ( ALLOCATED( surf_h(0)%ts )  .AND.  kk == 1 )         &
2352                         READ ( 13 )  surf_h(0)%ts
2353                   CASE ( 'surf_h(0)%qs' )         
2354                      IF ( ALLOCATED( surf_h(0)%qs )  .AND.  kk == 1 )         &
2355                         READ ( 13 )  surf_h(0)%qs
2356                   CASE ( 'surf_h(0)%ss' )         
2357                      IF ( ALLOCATED( surf_h(0)%ss )  .AND.  kk == 1 )         &
2358                         READ ( 13 )  surf_h(0)%ss
2359                   CASE ( 'surf_h(0)%qcs' )         
2360                      IF ( ALLOCATED( surf_h(0)%qcs )  .AND.  kk == 1 )        &
2361                         READ ( 13 )  surf_h(0)%qcs
2362                   CASE ( 'surf_h(0)%ncs' )         
2363                      IF ( ALLOCATED( surf_h(0)%ncs )  .AND.  kk == 1 )        &
2364                         READ ( 13 )  surf_h(0)%ncs
2365                   CASE ( 'surf_h(0)%qrs' )         
2366                      IF ( ALLOCATED( surf_h(0)%qrs )  .AND.  kk == 1 )        &
2367                         READ ( 13 )  surf_h(0)%qrs
2368                   CASE ( 'surf_h(0)%nrs' )         
2369                      IF ( ALLOCATED( surf_h(0)%nrs )  .AND.  kk == 1 )        &
2370                         READ ( 13 )  surf_h(0)%nrs
2371                   CASE ( 'surf_h(0)%ol' )         
2372                      IF ( ALLOCATED( surf_h(0)%ol )  .AND.  kk == 1 )         &
2373                         READ ( 13 )  surf_h(0)%ol
2374                   CASE ( 'surf_h(0)%rib' )         
2375                      IF ( ALLOCATED( surf_h(0)%rib )  .AND.  kk == 1 )        &
2376                         READ ( 13 )  surf_h(0)%rib
2377                   CASE ( 'surf_h(0)%usws' )         
2378                      IF ( ALLOCATED( surf_h(0)%usws )  .AND.  kk == 1 )       &
2379                         READ ( 13 )  surf_h(0)%usws
2380                   CASE ( 'surf_h(0)%vsws' )         
2381                      IF ( ALLOCATED( surf_h(0)%vsws )  .AND.  kk == 1 )       &
2382                         READ ( 13 )  surf_h(0)%vsws
2383                   CASE ( 'surf_h(0)%shf' )         
2384                      IF ( ALLOCATED( surf_h(0)%shf )  .AND.  kk == 1 )        &
2385                         READ ( 13 )  surf_h(0)%shf
2386                   CASE ( 'surf_h(0)%qsws' )         
2387                      IF ( ALLOCATED( surf_h(0)%qsws )  .AND.  kk == 1 )       &
2388                         READ ( 13 )  surf_h(0)%qsws
2389                   CASE ( 'surf_h(0)%ssws' )         
2390                      IF ( ALLOCATED( surf_h(0)%ssws )  .AND.  kk == 1 )       &
2391                         READ ( 13 )  surf_h(0)%ssws
2392                   CASE ( 'surf_h(0)%qcsws' )         
2393                      IF ( ALLOCATED( surf_h(0)%qcsws )  .AND.  kk == 1 )      &
2394                         READ ( 13 )  surf_h(0)%qcsws
2395                   CASE ( 'surf_h(0)%ncsws' )         
2396                      IF ( ALLOCATED( surf_h(0)%ncsws )  .AND.  kk == 1 )      &
2397                         READ ( 13 )  surf_h(0)%ncsws
2398                   CASE ( 'surf_h(0)%qrsws' )         
2399                      IF ( ALLOCATED( surf_h(0)%qrsws )  .AND.  kk == 1 )      &
2400                         READ ( 13 )  surf_h(0)%qrsws
2401                   CASE ( 'surf_h(0)%nrsws' )         
2402                      IF ( ALLOCATED( surf_h(0)%nrsws )  .AND.  kk == 1 )      &
2403                         READ ( 13 )  surf_h(0)%nrsws
2404                   CASE ( 'surf_h(0)%sasws' )         
2405                      IF ( ALLOCATED( surf_h(0)%sasws )  .AND.  kk == 1 )      &
2406                         READ ( 13 )  surf_h(0)%sasws
2407
2408                   CASE ( 'surf_h(1)%start_index' )   
2409                      IF ( kk == 1 )                                           &
2410                         READ ( 13 )  surf_h(1)%start_index
2411                      l = 1
2412                   CASE ( 'surf_h(1)%end_index' )   
2413                      IF ( kk == 1 )                                           &
2414                         READ ( 13 )  surf_h(1)%end_index
2415                   CASE ( 'surf_h(1)%us' )         
2416                      IF ( ALLOCATED( surf_h(1)%us )  .AND.  kk == 1 )         &
2417                         READ ( 13 )  surf_h(1)%us
2418                   CASE ( 'surf_h(1)%ts' )         
2419                      IF ( ALLOCATED( surf_h(1)%ts )  .AND.  kk == 1 )         &
2420                         READ ( 13 )  surf_h(1)%ts
2421                   CASE ( 'surf_h(1)%qs' )         
2422                      IF ( ALLOCATED( surf_h(1)%qs )  .AND.  kk == 1 )         &
2423                         READ ( 13 )  surf_h(1)%qs
2424                   CASE ( 'surf_h(1)%ss' )         
2425                      IF ( ALLOCATED( surf_h(1)%ss )  .AND.  kk == 1 )         &
2426                         READ ( 13 )  surf_h(1)%ss
2427                   CASE ( 'surf_h(1)%qcs' )         
2428                      IF ( ALLOCATED( surf_h(1)%qcs )  .AND.  kk == 1 )        &
2429                         READ ( 13 )  surf_h(1)%qcs
2430                   CASE ( 'surf_h(1)%ncs' )         
2431                      IF ( ALLOCATED( surf_h(1)%ncs )  .AND.  kk == 1 )        &
2432                         READ ( 13 )  surf_h(1)%ncs
2433                   CASE ( 'surf_h(1)%qrs' )         
2434                      IF ( ALLOCATED( surf_h(1)%qrs )  .AND.  kk == 1 )        &
2435                         READ ( 13 )  surf_h(1)%qrs
2436                   CASE ( 'surf_h(1)%nrs' )         
2437                      IF ( ALLOCATED( surf_h(1)%nrs )  .AND.  kk == 1 )        &
2438                         READ ( 13 )  surf_h(1)%nrs
2439                   CASE ( 'surf_h(1)%ol' )         
2440                      IF ( ALLOCATED( surf_h(1)%ol )  .AND.  kk == 1 )         &
2441                         READ ( 13 )  surf_h(1)%ol
2442                   CASE ( 'surf_h(1)%rib' )         
2443                      IF ( ALLOCATED( surf_h(1)%rib )  .AND.  kk == 1 )        &
2444                         READ ( 13 )  surf_h(1)%rib
2445                   CASE ( 'surf_h(1)%usws' )         
2446                      IF ( ALLOCATED( surf_h(1)%usws )  .AND.  kk == 1 )       &
2447                         READ ( 13 )  surf_h(1)%usws
2448                   CASE ( 'surf_h(1)%vsws' )         
2449                      IF ( ALLOCATED( surf_h(1)%vsws )  .AND.  kk == 1 )       &
2450                         READ ( 13 )  surf_h(1)%vsws
2451                   CASE ( 'surf_h(1)%shf' )         
2452                      IF ( ALLOCATED( surf_h(1)%shf )  .AND.  kk == 1 )        &
2453                         READ ( 13 )  surf_h(1)%shf
2454                   CASE ( 'surf_h(1)%qsws' )         
2455                      IF ( ALLOCATED( surf_h(1)%qsws )  .AND.  kk == 1 )       &
2456                         READ ( 13 )  surf_h(1)%qsws
2457                   CASE ( 'surf_h(1)%ssws' )         
2458                      IF ( ALLOCATED( surf_h(1)%ssws )  .AND.  kk == 1 )       &
2459                         READ ( 13 )  surf_h(1)%ssws
2460                   CASE ( 'surf_h(1)%qcsws' )         
2461                      IF ( ALLOCATED( surf_h(1)%qcsws )  .AND.  kk == 1 )      &
2462                         READ ( 13 )  surf_h(1)%qcsws
2463                   CASE ( 'surf_h(1)%ncsws' )         
2464                      IF ( ALLOCATED( surf_h(1)%ncsws )  .AND.  kk == 1 )      &
2465                         READ ( 13 )  surf_h(1)%ncsws
2466                   CASE ( 'surf_h(1)%qrsws' )         
2467                      IF ( ALLOCATED( surf_h(1)%qrsws )  .AND.  kk == 1 )      &
2468                         READ ( 13 )  surf_h(1)%qrsws
2469                   CASE ( 'surf_h(1)%nrsws' )         
2470                      IF ( ALLOCATED( surf_h(1)%nrsws )  .AND.  kk == 1 )      &
2471                         READ ( 13 )  surf_h(1)%nrsws
2472                   CASE ( 'surf_h(1)%sasws' )         
2473                      IF ( ALLOCATED( surf_h(1)%sasws )  .AND.  kk == 1 )      &
2474                         READ ( 13 )  surf_h(1)%sasws
2475
2476                   CASE ( 'surf_h(2)%start_index' )   
2477                      IF ( kk == 1 )                                           &
2478                         READ ( 13 )  surf_h(2)%start_index
2479                      l = 2
2480                   CASE ( 'surf_h(2)%end_index' )   
2481                      IF ( kk == 1 )                                           &
2482                         READ ( 13 )  surf_h(2)%end_index
2483                   CASE ( 'surf_h(2)%us' )         
2484                      IF ( ALLOCATED( surf_h(2)%us )  .AND.  kk == 1 )         &
2485                         READ ( 13 )  surf_h(2)%us
2486                   CASE ( 'surf_h(2)%ts' )         
2487                      IF ( ALLOCATED( surf_h(2)%ts )  .AND.  kk == 1 )         &
2488                         READ ( 13 )  surf_h(2)%ts
2489                   CASE ( 'surf_h(2)%qs' )       
2490                      IF ( ALLOCATED( surf_h(2)%qs )  .AND.  kk == 1 )         &
2491                         READ ( 13 )  surf_h(2)%qs
2492                   CASE ( 'surf_h(2)%ss' )         
2493                      IF ( ALLOCATED( surf_h(2)%ss )  .AND.  kk == 1 )         &
2494                         READ ( 13 )  surf_h(2)%ss
2495                   CASE ( 'surf_h(2)%qcs' )         
2496                      IF ( ALLOCATED( surf_h(2)%qcs )  .AND.  kk == 1 )        &
2497                         READ ( 13 )  surf_h(2)%qcs
2498                   CASE ( 'surf_h(2)%ncs' )         
2499                      IF ( ALLOCATED( surf_h(2)%ncs )  .AND.  kk == 1 )        &
2500                         READ ( 13 )  surf_h(2)%ncs
2501                   CASE ( 'surf_h(2)%qrs' )         
2502                      IF ( ALLOCATED( surf_h(2)%qrs )  .AND.  kk == 1 )        &
2503                         READ ( 13 )  surf_h(2)%qrs
2504                   CASE ( 'surf_h(2)%nrs' )         
2505                      IF ( ALLOCATED( surf_h(2)%nrs )  .AND.  kk == 1 )        &
2506                         READ ( 13 )  surf_h(2)%nrs
2507                   CASE ( 'surf_h(2)%ol' )         
2508                      IF ( ALLOCATED( surf_h(2)%ol )  .AND.  kk == 1 )         &
2509                         READ ( 13 )  surf_h(2)%ol
2510                   CASE ( 'surf_h(2)%rib' )         
2511                      IF ( ALLOCATED( surf_h(2)%rib )  .AND.  kk == 1 )        &
2512                         READ ( 13 )  surf_h(2)%rib
2513                   CASE ( 'surf_h(2)%usws' )         
2514                      IF ( ALLOCATED( surf_h(2)%usws )  .AND.  kk == 1 )       &
2515                         READ ( 13 )  surf_h(2)%usws
2516                   CASE ( 'surf_h(2)%vsws' )         
2517                      IF ( ALLOCATED( surf_h(2)%vsws )  .AND.  kk == 1 )       &
2518                         READ ( 13 )  surf_h(2)%vsws
2519                   CASE ( 'surf_h(2)%shf' )         
2520                      IF ( ALLOCATED( surf_h(2)%shf )  .AND.  kk == 1 )        &
2521                         READ ( 13 )  surf_h(2)%shf
2522                   CASE ( 'surf_h(2)%qsws' )         
2523                      IF ( ALLOCATED( surf_h(2)%qsws )  .AND.  kk == 1 )       &
2524                         READ ( 13 )  surf_h(2)%qsws
2525                   CASE ( 'surf_h(2)%ssws' )         
2526                      IF ( ALLOCATED( surf_h(2)%ssws )  .AND.  kk == 1 )       &
2527                         READ ( 13 )  surf_h(2)%ssws
2528                   CASE ( 'surf_h(2)%qcsws' )         
2529                      IF ( ALLOCATED( surf_h(2)%qcsws )  .AND.  kk == 1 )      &
2530                         READ ( 13 )  surf_h(2)%qcsws
2531                   CASE ( 'surf_h(2)%ncsws' )         
2532                      IF ( ALLOCATED( surf_h(2)%ncsws )  .AND.  kk == 1 )      &
2533                         READ ( 13 )  surf_h(2)%ncsws
2534                   CASE ( 'surf_h(2)%qrsws' )         
2535                      IF ( ALLOCATED( surf_h(2)%qrsws )  .AND.  kk == 1 )      &
2536                         READ ( 13 )  surf_h(2)%qrsws
2537                   CASE ( 'surf_h(2)%nrsws' )         
2538                      IF ( ALLOCATED( surf_h(2)%nrsws )  .AND.  kk == 1 )      &
2539                         READ ( 13 )  surf_h(2)%nrsws
2540                   CASE ( 'surf_h(2)%sasws' )         
2541                      IF ( ALLOCATED( surf_h(2)%sasws )  .AND.  kk == 1 )      &
2542                         READ ( 13 )  surf_h(2)%sasws
2543
2544                   CASE ( 'surf_v(0)%start_index' )   
2545                      IF ( kk == 1 )                                           &
2546                         READ ( 13 )  surf_v(0)%start_index
2547                      l = 0
2548                      horizontal_surface = .FALSE.
2549                      vertical_surface   = .TRUE.
2550                   CASE ( 'surf_v(0)%end_index' )   
2551                      IF ( kk == 1 )                                           &
2552                         READ ( 13 )  surf_v(0)%end_index
2553                   CASE ( 'surf_v(0)%us' )         
2554                      IF ( ALLOCATED( surf_v(0)%us )  .AND.  kk == 1 )         &
2555                         READ ( 13 )  surf_v(0)%us
2556                   CASE ( 'surf_v(0)%ts' )         
2557                      IF ( ALLOCATED( surf_v(0)%ts )  .AND.  kk == 1 )         &
2558                         READ ( 13 )  surf_v(0)%ts
2559                   CASE ( 'surf_v(0)%qs' )         
2560                      IF ( ALLOCATED( surf_v(0)%qs )  .AND.  kk == 1 )         &
2561                         READ ( 13 )  surf_v(0)%qs
2562                   CASE ( 'surf_v(0)%ss' )         
2563                      IF ( ALLOCATED( surf_v(0)%ss )  .AND.  kk == 1 )         &
2564                         READ ( 13 )  surf_v(0)%ss
2565                   CASE ( 'surf_v(0)%qcs' )         
2566                      IF ( ALLOCATED( surf_v(0)%qcs )  .AND.  kk == 1 )        &
2567                         READ ( 13 )  surf_v(0)%qcs
2568                   CASE ( 'surf_v(0)%ncs' )         
2569                      IF ( ALLOCATED( surf_v(0)%ncs )  .AND.  kk == 1 )        &
2570                         READ ( 13 )  surf_v(0)%ncs
2571                   CASE ( 'surf_v(0)%qrs' )         
2572                      IF ( ALLOCATED( surf_v(0)%qrs )  .AND.  kk == 1 )        &
2573                         READ ( 13 )  surf_v(0)%qrs
2574                   CASE ( 'surf_v(0)%nrs' )         
2575                      IF ( ALLOCATED( surf_v(0)%nrs )  .AND.  kk == 1 )        &
2576                         READ ( 13 )  surf_v(0)%nrs
2577                   CASE ( 'surf_v(0)%ol' )         
2578                      IF ( ALLOCATED( surf_v(0)%ol )  .AND.  kk == 1 )         &
2579                         READ ( 13 )  surf_v(0)%ol
2580                   CASE ( 'surf_v(0)%rib' )         
2581                      IF ( ALLOCATED( surf_v(0)%rib )  .AND.  kk == 1 )        &
2582                         READ ( 13 )  surf_v(0)%rib
2583                   CASE ( 'surf_v(0)%shf' )         
2584                      IF ( ALLOCATED( surf_v(0)%shf )  .AND.  kk == 1 )        &
2585                         READ ( 13 )  surf_v(0)%shf
2586                   CASE ( 'surf_v(0)%qsws' )         
2587                      IF ( ALLOCATED( surf_v(0)%qsws )  .AND.  kk == 1 )       &
2588                         READ ( 13 )  surf_v(0)%qsws
2589                   CASE ( 'surf_v(0)%ssws' )         
2590                      IF ( ALLOCATED( surf_v(0)%ssws )  .AND.  kk == 1 )       &
2591                         READ ( 13 )  surf_v(0)%ssws
2592                   CASE ( 'surf_v(0)%qcsws' )         
2593                      IF ( ALLOCATED( surf_v(0)%qcsws )  .AND.  kk == 1 )      &
2594                         READ ( 13 )  surf_v(0)%qcsws
2595                   CASE ( 'surf_v(0)%ncsws' )         
2596                      IF ( ALLOCATED( surf_v(0)%ncsws )  .AND.  kk == 1 )      &
2597                         READ ( 13 )  surf_v(0)%ncsws
2598                   CASE ( 'surf_v(0)%qrsws' )         
2599                      IF ( ALLOCATED( surf_v(0)%qrsws )  .AND.  kk == 1 )      &
2600                         READ ( 13 )  surf_v(0)%qrsws
2601                   CASE ( 'surf_v(0)%nrsws' )         
2602                      IF ( ALLOCATED( surf_v(0)%nrsws )  .AND.  kk == 1 )      &
2603                         READ ( 13 )  surf_v(0)%nrsws
2604                   CASE ( 'surf_v(0)%sasws' )         
2605                      IF ( ALLOCATED( surf_v(0)%sasws )  .AND.  kk == 1 )      &
2606                         READ ( 13 )  surf_v(0)%sasws
2607                   CASE ( 'surf_v(0)%mom_uv' )         
2608                      IF ( ALLOCATED( surf_v(0)%mom_flux_uv )  .AND.  kk == 1 )&
2609                         READ ( 13 )  surf_v(0)%mom_flux_uv
2610                   CASE ( 'surf_v(0)%mom_w' )         
2611                      IF ( ALLOCATED( surf_v(0)%mom_flux_w )  .AND.  kk == 1 ) &
2612                         READ ( 13 )  surf_v(0)%mom_flux_w
2613                   CASE ( 'surf_v(0)%mom_tke' )         
2614                      IF ( ALLOCATED( surf_v(0)%mom_flux_tke )  .AND.  kk == 1 )&
2615                         READ ( 13 )  surf_v(0)%mom_flux_tke
2616
2617                   CASE ( 'surf_v(1)%start_index' )   
2618                      IF ( kk == 1 )                                           &
2619                         READ ( 13 )  surf_v(1)%start_index
2620                      l = 1
2621                   CASE ( 'surf_v(1)%end_index' )   
2622                      IF ( kk == 1 )                                           &
2623                         READ ( 13 )  surf_v(1)%end_index
2624                   CASE ( 'surf_v(1)%us' )         
2625                      IF ( ALLOCATED( surf_v(1)%us )  .AND.  kk == 1 )         &
2626                         READ ( 13 )  surf_v(1)%us
2627                   CASE ( 'surf_v(1)%ts' )         
2628                      IF ( ALLOCATED( surf_v(1)%ts )  .AND.  kk == 1 )         &
2629                         READ ( 13 )  surf_v(1)%ts
2630                   CASE ( 'surf_v(1)%qs' )         
2631                      IF ( ALLOCATED( surf_v(1)%qs )  .AND.  kk == 1 )         &
2632                         READ ( 13 )  surf_v(1)%qs
2633                   CASE ( 'surf_v(1)%ss' )         
2634                      IF ( ALLOCATED( surf_v(1)%ss )  .AND.  kk == 1 )         &
2635                         READ ( 13 )  surf_v(1)%ss
2636                   CASE ( 'surf_v(1)%qcs' )         
2637                      IF ( ALLOCATED( surf_v(1)%qcs )  .AND.  kk == 1 )        &
2638                         READ ( 13 )  surf_v(1)%qcs
2639                   CASE ( 'surf_v(1)%ncs' )         
2640                      IF ( ALLOCATED( surf_v(1)%ncs )  .AND.  kk == 1 )        &
2641                         READ ( 13 )  surf_v(1)%ncs
2642                   CASE ( 'surf_v(1)%qrs' )         
2643                      IF ( ALLOCATED( surf_v(1)%qrs )  .AND.  kk == 1 )        &
2644                         READ ( 13 )  surf_v(1)%qrs
2645                   CASE ( 'surf_v(1)%nrs' )         
2646                      IF ( ALLOCATED( surf_v(1)%nrs )  .AND.  kk == 1 )        &
2647                         READ ( 13 )  surf_v(1)%nrs
2648                   CASE ( 'surf_v(1)%ol' )         
2649                      IF ( ALLOCATED( surf_v(1)%ol )  .AND.  kk == 1 )         &
2650                         READ ( 13 )  surf_v(1)%ol
2651                   CASE ( 'surf_v(1)%rib' )         
2652                      IF ( ALLOCATED( surf_v(1)%rib )  .AND.  kk == 1 )        &
2653                         READ ( 13 )  surf_v(1)%rib
2654                   CASE ( 'surf_v(1)%shf' )         
2655                      IF ( ALLOCATED( surf_v(1)%shf )  .AND.  kk == 1 )        &
2656                         READ ( 13 )  surf_v(1)%shf
2657                   CASE ( 'surf_v(1)%qsws' )         
2658                      IF ( ALLOCATED( surf_v(1)%qsws )  .AND.  kk == 1 )       &
2659                         READ ( 13 )  surf_v(1)%qsws
2660                   CASE ( 'surf_v(1)%ssws' )         
2661                      IF ( ALLOCATED( surf_v(1)%ssws )  .AND.  kk == 1 )       &
2662                         READ ( 13 )  surf_v(1)%ssws
2663                   CASE ( 'surf_v(1)%qcsws' )         
2664                      IF ( ALLOCATED( surf_v(1)%qcsws )  .AND.  kk == 1 )      &
2665                         READ ( 13 )  surf_v(1)%qcsws
2666                   CASE ( 'surf_v(1)%ncsws' )         
2667                      IF ( ALLOCATED( surf_v(1)%ncsws )  .AND.  kk == 1 )      &
2668                         READ ( 13 )  surf_v(1)%ncsws
2669                   CASE ( 'surf_v(1)%qrsws' )         
2670                      IF ( ALLOCATED( surf_v(1)%qrsws )  .AND.  kk == 1 )      &
2671                         READ ( 13 )  surf_v(1)%qrsws
2672                   CASE ( 'surf_v(1)%nrsws' )         
2673                      IF ( ALLOCATED( surf_v(1)%nrsws )  .AND.  kk == 1 )      &
2674                         READ ( 13 )  surf_v(1)%nrsws
2675                   CASE ( 'surf_v(1)%sasws' )         
2676                      IF ( ALLOCATED( surf_v(1)%sasws )  .AND.  kk == 1 )      &
2677                         READ ( 13 )  surf_v(1)%sasws
2678                   CASE ( 'surf_v(1)%mom_uv' )         
2679                      IF ( ALLOCATED( surf_v(1)%mom_flux_uv )  .AND.  kk == 1 )&
2680                         READ ( 13 )  surf_v(1)%mom_flux_uv
2681                   CASE ( 'surf_v(1)%mom_w' )         
2682                      IF ( ALLOCATED( surf_v(1)%mom_flux_w )  .AND.  kk == 1 ) &
2683                         READ ( 13 )  surf_v(1)%mom_flux_w
2684                   CASE ( 'surf_v(1)%mom_tke' )         
2685                      IF ( ALLOCATED( surf_v(1)%mom_flux_tke )  .AND.  kk == 1 )&
2686                         READ ( 13 )  surf_v(1)%mom_flux_tke
2687
2688                   CASE ( 'surf_v(2)%start_index' )   
2689                      IF ( kk == 1 )                                           &
2690                         READ ( 13 )  surf_v(2)%start_index
2691                      l = 2
2692                   CASE ( 'surf_v(2)%end_index' )   
2693                      IF ( kk == 1 )                                           &
2694                         READ ( 13 )  surf_v(2)%end_index
2695                   CASE ( 'surf_v(2)%us' )         
2696                      IF ( ALLOCATED( surf_v(2)%us )  .AND.  kk == 1 )         &
2697                         READ ( 13 )  surf_v(2)%us
2698                   CASE ( 'surf_v(2)%ts' )         
2699                      IF ( ALLOCATED( surf_v(2)%ts )  .AND.  kk == 1 )         &
2700                         READ ( 13 )  surf_v(2)%ts
2701                   CASE ( 'surf_v(2)%qs' )         
2702                      IF ( ALLOCATED( surf_v(2)%qs )  .AND.  kk == 1 )         &
2703                         READ ( 13 )  surf_v(2)%qs
2704                   CASE ( 'surf_v(2)%ss' )         
2705                      IF ( ALLOCATED( surf_v(2)%ss )  .AND.  kk == 1 )         &
2706                         READ ( 13 )  surf_v(2)%ss
2707                   CASE ( 'surf_v(2)%qcs' )         
2708                      IF ( ALLOCATED( surf_v(2)%qcs )  .AND.  kk == 1 )        &
2709                         READ ( 13 )  surf_v(2)%qcs
2710                   CASE ( 'surf_v(2)%ncs' )         
2711                      IF ( ALLOCATED( surf_v(2)%ncs )  .AND.  kk == 1 )        &
2712                         READ ( 13 )  surf_v(2)%ncs
2713                   CASE ( 'surf_v(2)%qrs' )         
2714                      IF ( ALLOCATED( surf_v(2)%qrs )  .AND.  kk == 1 )        &
2715                         READ ( 13 )  surf_v(2)%qrs
2716                   CASE ( 'surf_v(2)%nrs' )         
2717                      IF ( ALLOCATED( surf_v(2)%nrs )  .AND.  kk == 1 )        &
2718                         READ ( 13 )  surf_v(2)%nrs
2719                   CASE ( 'surf_v(2)%ol' )         
2720                      IF ( ALLOCATED( surf_v(2)%ol )  .AND.  kk == 1 )         &
2721                         READ ( 13 )  surf_v(2)%ol
2722                   CASE ( 'surf_v(2)%rib' )         
2723                      IF ( ALLOCATED( surf_v(2)%rib )  .AND.  kk == 1 )        &
2724                         READ ( 13 )  surf_v(2)%rib
2725                   CASE ( 'surf_v(2)%shf' )         
2726                      IF ( ALLOCATED( surf_v(2)%shf )  .AND.  kk == 1 )        &
2727                         READ ( 13 )  surf_v(2)%shf
2728                   CASE ( 'surf_v(2)%qsws' )         
2729                      IF ( ALLOCATED( surf_v(2)%qsws )  .AND.  kk == 1 )       &
2730                         READ ( 13 )  surf_v(2)%qsws
2731                   CASE ( 'surf_v(2)%ssws' )         
2732                      IF ( ALLOCATED( surf_v(2)%ssws )  .AND.  kk == 1 )       &
2733                         READ ( 13 )  surf_v(2)%ssws
2734                   CASE ( 'surf_v(2)%qcsws' )         
2735                      IF ( ALLOCATED( surf_v(2)%qcsws )  .AND.  kk == 1 )      &
2736                         READ ( 13 )  surf_v(2)%qcsws
2737                   CASE ( 'surf_v(2)%ncsws' )         
2738                      IF ( ALLOCATED( surf_v(2)%ncsws )  .AND.  kk == 1 )      &
2739                         READ ( 13 )  surf_v(2)%ncsws
2740                   CASE ( 'surf_v(2)%qrsws' )         
2741                      IF ( ALLOCATED( surf_v(2)%qrsws )  .AND.  kk == 1 )      &
2742                         READ ( 13 )  surf_v(2)%qrsws
2743                   CASE ( 'surf_v(2)%nrsws' )         
2744                      IF ( ALLOCATED( surf_v(2)%nrsws )  .AND.  kk == 1 )      &
2745                         READ ( 13 )  surf_v(2)%nrsws
2746                   CASE ( 'surf_v(2)%sasws' )         
2747                      IF ( ALLOCATED( surf_v(2)%sasws )  .AND.  kk == 1 )      &
2748                         READ ( 13 )  surf_v(2)%sasws
2749                   CASE ( 'surf_v(2)%mom_uv' )         
2750                      IF ( ALLOCATED( surf_v(2)%mom_flux_uv )  .AND.  kk == 1 )&
2751                         READ ( 13 )  surf_v(2)%mom_flux_uv
2752                   CASE ( 'surf_v(2)%mom_w' )         
2753                      IF ( ALLOCATED( surf_v(2)%mom_flux_w )  .AND.  kk == 1 ) &
2754                         READ ( 13 )  surf_v(2)%mom_flux_w
2755                   CASE ( 'surf_v(2)%mom_tke' )         
2756                      IF ( ALLOCATED( surf_v(2)%mom_flux_tke )  .AND.  kk == 1 )&
2757                         READ ( 13 )  surf_v(2)%mom_flux_tke
2758
2759                   CASE ( 'surf_v(3)%start_index' )   
2760                      IF ( kk == 1 )                                           &
2761                         READ ( 13 )  surf_v(3)%start_index
2762                      l = 3
2763                   CASE ( 'surf_v(3)%end_index' )   
2764                      IF ( kk == 1 )                                           &
2765                         READ ( 13 )  surf_v(3)%end_index
2766                   CASE ( 'surf_v(3)%us' )         
2767                      IF ( ALLOCATED( surf_v(3)%us )  .AND.  kk == 1 )         &
2768                         READ ( 13 )  surf_v(3)%us
2769                   CASE ( 'surf_v(3)%ts' )         
2770                      IF ( ALLOCATED( surf_v(3)%ts )  .AND.  kk == 1 )         &
2771                         READ ( 13 )  surf_v(3)%ts
2772                   CASE ( 'surf_v(3)%qs' )       
2773                      IF ( ALLOCATED( surf_v(3)%qs )  .AND.  kk == 1 )         &
2774                         READ ( 13 )  surf_v(3)%qs
2775                   CASE ( 'surf_v(3)%ss' )         
2776                      IF ( ALLOCATED( surf_v(3)%ss )  .AND.  kk == 1 )         &
2777                         READ ( 13 )  surf_v(3)%ss
2778                   CASE ( 'surf_v(3)%qcs' )         
2779                      IF ( ALLOCATED( surf_v(3)%qcs )  .AND.  kk == 1 )        &
2780                         READ ( 13 )  surf_v(3)%qcs
2781                   CASE ( 'surf_v(3)%ncs' )         
2782                      IF ( ALLOCATED( surf_v(3)%ncs )  .AND.  kk == 1 )        &
2783                         READ ( 13 )  surf_v(3)%ncs
2784                   CASE ( 'surf_v(3)%qrs' )         
2785                      IF ( ALLOCATED( surf_v(3)%qrs )  .AND.  kk == 1 )        &
2786                         READ ( 13 )  surf_v(3)%qrs
2787                   CASE ( 'surf_v(3)%nrs' )         
2788                      IF ( ALLOCATED( surf_v(3)%nrs )  .AND.  kk == 1 )        &
2789                         READ ( 13 )  surf_v(3)%nrs
2790                   CASE ( 'surf_v(3)%ol' )         
2791                      IF ( ALLOCATED( surf_v(3)%ol )  .AND.  kk == 1 )         &
2792                         READ ( 13 )  surf_v(3)%ol
2793                   CASE ( 'surf_v(3)%rib' )         
2794                      IF ( ALLOCATED( surf_v(3)%rib )  .AND.  kk == 1 )        &
2795                         READ ( 13 )  surf_v(3)%rib
2796                   CASE ( 'surf_v(3)%shf' )         
2797                      IF ( ALLOCATED( surf_v(3)%shf )  .AND.  kk == 1 )        &
2798                         READ ( 13 )  surf_v(3)%shf
2799                   CASE ( 'surf_v(3)%qsws' )         
2800                      IF ( ALLOCATED( surf_v(3)%qsws )  .AND.  kk == 1 )       &
2801                         READ ( 13 )  surf_v(3)%qsws
2802                   CASE ( 'surf_v(3)%ssws' )         
2803                      IF ( ALLOCATED( surf_v(3)%ssws )  .AND.  kk == 1 )       &
2804                         READ ( 13 )  surf_v(3)%ssws
2805                   CASE ( 'surf_v(3)%qcsws' )         
2806                      IF ( ALLOCATED( surf_v(3)%qcsws )  .AND.  kk == 1 )      &
2807                         READ ( 13 )  surf_v(3)%qcsws
2808                   CASE ( 'surf_v(3)%ncsws' )         
2809                      IF ( ALLOCATED( surf_v(3)%ncsws )  .AND.  kk == 1 )      &
2810                         READ ( 13 )  surf_v(3)%ncsws
2811                   CASE ( 'surf_v(3)%qrsws' )         
2812                      IF ( ALLOCATED( surf_v(3)%qrsws )  .AND.  kk == 1 )      &
2813                         READ ( 13 )  surf_v(3)%qrsws
2814                   CASE ( 'surf_v(3)%nrsws' )         
2815                      IF ( ALLOCATED( surf_v(3)%nrsws )  .AND.  kk == 1 )      &
2816                         READ ( 13 )  surf_v(3)%nrsws
2817                   CASE ( 'surf_v(3)%sasws' )         
2818                      IF ( ALLOCATED( surf_v(3)%sasws )  .AND.  kk == 1 )      &
2819                         READ ( 13 )  surf_v(3)%sasws
2820                   CASE ( 'surf_v(3)%mom_uv' )         
2821                      IF ( ALLOCATED( surf_v(3)%mom_flux_uv )  .AND.  kk == 1 )&
2822                         READ ( 13 )  surf_v(3)%mom_flux_uv
2823                   CASE ( 'surf_v(3)%mom_w' )         
2824                      IF ( ALLOCATED( surf_v(3)%mom_flux_w )  .AND.  kk == 1 ) &
2825                         READ ( 13 )  surf_v(3)%mom_flux_w
2826                   CASE ( 'surf_v(3)%mom_tke' )         
2827                      IF ( ALLOCATED( surf_v(3)%mom_flux_tke )  .AND.  kk == 1 )&
2828                         READ ( 13 )  surf_v(3)%mom_flux_tke
2829
2830                END SELECT
2831!
2832!--             Redistribute surface elements on its respective type.
2833                IF ( horizontal_surface )  THEN
2834                   ic = nxlc
2835                   DO  i = nxlf, nxrf
2836                      jc = nysc
2837                      DO  j = nysf, nynf
2838
2839                         surf_match_def  = surf_def_h(l)%end_index(jc,ic) >=   &
2840                                           surf_def_h(l)%start_index(jc,ic)
2841                         surf_match_lsm  = surf_lsm_h%end_index(jc,ic)    >=   &
2842                                           surf_lsm_h%start_index(jc,ic)
2843                         surf_match_usm  = surf_usm_h%end_index(jc,ic)    >=   &
2844                                           surf_usm_h%start_index(jc,ic)
2845
2846                         IF ( surf_match_def )  THEN
2847                            mm = surf_def_h(l)%start_index(jc,ic)
2848                            DO  m = surf_h(l)%start_index(j,i),                &
2849                                    surf_h(l)%end_index(j,i)
2850                               CALL restore_surface_elements( surf_def_h(l),   &
2851                                                              mm, surf_h(l), m )
2852                               mm = mm + 1
2853                            ENDDO
2854                         ENDIF
2855
2856                         IF ( surf_match_lsm )  THEN
2857                            mm = surf_lsm_h%start_index(jc,ic)
2858                            DO  m = surf_h(l)%start_index(j,i),                &
2859                                    surf_h(l)%end_index(j,i)
2860                               CALL restore_surface_elements( surf_lsm_h,      &
2861                                                              mm, surf_h(l), m )
2862                               mm = mm + 1
2863                            ENDDO
2864                         ENDIF
2865
2866                         IF ( surf_match_usm )  THEN
2867                            mm = surf_usm_h%start_index(jc,ic)
2868                            DO  m = surf_h(l)%start_index(j,i),                &
2869                                    surf_h(l)%end_index(j,i)
2870                               CALL restore_surface_elements( surf_usm_h,      &
2871                                                              mm, surf_h(l), m )
2872                               mm = mm + 1
2873                            ENDDO
2874                         ENDIF
2875
2876                         jc = jc + 1
2877                      ENDDO
2878                      ic = ic + 1
2879                   ENDDO
2880                ELSEIF ( vertical_surface )  THEN
2881                   ic = nxlc
2882                   DO  i = nxlf, nxrf
2883                      jc = nysc
2884                      DO  j = nysf, nynf
2885
2886                         surf_match_def  = surf_def_v(l)%end_index(jc,ic) >=   &
2887                                           surf_def_v(l)%start_index(jc,ic)
2888                         surf_match_lsm  = surf_lsm_v(l)%end_index(jc,ic) >=   &
2889                                           surf_lsm_v(l)%start_index(jc,ic)
2890                         surf_match_usm  = surf_usm_v(l)%end_index(jc,ic) >=   &
2891                                           surf_usm_v(l)%start_index(jc,ic)
2892
2893
2894
2895                         IF ( surf_match_def )  THEN
2896                            mm = surf_def_v(l)%start_index(jc,ic)
2897                            DO  m = surf_v(l)%start_index(j,i),                &
2898                                    surf_v(l)%end_index(j,i)
2899                               CALL restore_surface_elements( surf_def_v(l),   &
2900                                                              mm, surf_v(l), m )
2901                               mm = mm + 1
2902                            ENDDO
2903                         ENDIF
2904
2905                         IF ( surf_match_lsm )  THEN
2906                            mm = surf_lsm_v(l)%start_index(jc,ic)
2907                            DO  m = surf_v(l)%start_index(j,i),                &
2908                                    surf_v(l)%end_index(j,i)
2909                               CALL restore_surface_elements( surf_lsm_v(l),   &
2910                                                              mm, surf_v(l), m )
2911                               mm = mm + 1
2912                            ENDDO
2913                         ENDIF
2914   
2915                         IF ( surf_match_usm )  THEN
2916                            mm = surf_usm_v(l)%start_index(jc,ic)
2917                            DO  m = surf_v(l)%start_index(j,i),                &
2918                                    surf_v(l)%end_index(j,i)
2919                               CALL restore_surface_elements( surf_usm_v(l),   &
2920                                                              mm, surf_v(l), m )
2921                               mm = mm + 1
2922                            ENDDO
2923                         ENDIF
2924
2925                         jc = jc + 1
2926                      ENDDO
2927                      ic = ic + 1
2928                   ENDDO
2929                ENDIF
2930
2931             ENDDO
2932
2933             READ ( 13 )  field_chr
2934
2935          ENDDO
2936
2937       ENDIF
2938
2939
2940       CONTAINS
2941!------------------------------------------------------------------------------!
2942! Description:
2943! ------------
2944!> Restores surfacle elements back on its respective type.
2945!------------------------------------------------------------------------------!
2946          SUBROUTINE restore_surface_elements( surf_target, m_target,          &
2947                                               surf_file,   m_file )
2948
2949             IMPLICIT NONE
2950
2951             INTEGER(iwp)      ::  m_file      !< respective surface-element index of current surface array
2952             INTEGER(iwp)      ::  m_target    !< respecitve surface-element index of surface array on file
2953
2954             TYPE( surf_type ) ::  surf_target !< target surface type
2955             TYPE( surf_type ) ::  surf_file   !< surface type on file
2956
2957             IF ( SCAN( TRIM( field_chr ), '%us' ) /= 0 )  THEN
2958                IF ( ALLOCATED( surf_target%us )  .AND.                        &
2959                     ALLOCATED( surf_file%us   ) )                             & 
2960                   surf_target%us(m_target) = surf_file%us(m_file)
2961             ENDIF
2962
2963             IF ( SCAN( TRIM( field_chr ), '%ol' ) /= 0 )  THEN
2964                IF ( ALLOCATED( surf_target%ol )  .AND.                        &
2965                     ALLOCATED( surf_file%ol   ) )                             & 
2966                   surf_target%ol(m_target) = surf_file%ol(m_file)
2967             ENDIF
2968
2969             IF ( SCAN( TRIM( field_chr ), '%usws' ) /= 0 )  THEN
2970                IF ( ALLOCATED( surf_target%usws )  .AND.                      &
2971                     ALLOCATED( surf_file%usws   ) )                           & 
2972                   surf_target%usws(m_target) = surf_file%usws(m_file)
2973             ENDIF
2974
2975             IF ( SCAN( TRIM( field_chr ), '%vsws' ) /= 0 )  THEN
2976                IF ( ALLOCATED( surf_target%vsws )  .AND.                      &
2977                     ALLOCATED( surf_file%vsws   ) )                           & 
2978                   surf_target%vsws(m_target) = surf_file%vsws(m_file)
2979             ENDIF
2980
2981             IF ( SCAN( TRIM( field_chr ), '%ts' ) /= 0 )  THEN
2982                IF ( ALLOCATED( surf_target%ts )  .AND.                        &
2983                     ALLOCATED( surf_file%ts   ) )                             & 
2984                   surf_target%ts(m_target) = surf_file%ts(m_file)
2985             ENDIF
2986
2987             IF ( SCAN( TRIM( field_chr ), '%shf' ) /= 0 )  THEN
2988                IF ( ALLOCATED( surf_target%shf )  .AND.                       &
2989                     ALLOCATED( surf_file%shf   ) )                            & 
2990                   surf_target%shf(m_target) = surf_file%shf(m_file)
2991             ENDIF
2992
2993             IF ( SCAN( TRIM( field_chr ), '%qs' ) /= 0 )  THEN
2994                IF ( ALLOCATED( surf_target%qs )  .AND.                        &
2995                     ALLOCATED( surf_file%qs   ) )                             & 
2996                   surf_target%qs(m_target) = surf_file%qs(m_file)
2997             ENDIF
2998
2999             IF ( SCAN( TRIM( field_chr ), '%qsws' ) /= 0 )  THEN
3000                IF ( ALLOCATED( surf_target%qsws )  .AND.                      &
3001                     ALLOCATED( surf_file%qsws   ) )                           & 
3002                   surf_target%qsws(m_target) = surf_file%qsws(m_file)
3003             ENDIF
3004
3005             IF ( SCAN( TRIM( field_chr ), '%ss' ) /= 0 )  THEN
3006                IF ( ALLOCATED( surf_target%ss )  .AND.                        &
3007                     ALLOCATED( surf_file%ss   ) )                             & 
3008                   surf_target%ss(m_target) = surf_file%ss(m_file)
3009             ENDIF
3010
3011             IF ( SCAN( TRIM( field_chr ), '%ssws' ) /= 0 )  THEN
3012                IF ( ALLOCATED( surf_target%ssws )  .AND.                      &
3013                     ALLOCATED( surf_file%ssws   ) )                           & 
3014                   surf_target%ssws(m_target) = surf_file%ssws(m_file)
3015             ENDIF
3016
3017             IF ( SCAN( TRIM( field_chr ), '%qcs' ) /= 0 )  THEN
3018                IF ( ALLOCATED( surf_target%qcs )  .AND.                       &
3019                     ALLOCATED( surf_file%qcs   ) )                            & 
3020                  surf_target%qcs(m_target) = surf_file%qcs(m_file)
3021             ENDIF
3022
3023             IF ( SCAN( TRIM( field_chr ), '%qcsws' ) /= 0 )  THEN
3024                IF ( ALLOCATED( surf_target%qcsws )  .AND.                     &
3025                     ALLOCATED( surf_file%qcsws   ) )                          & 
3026                   surf_target%qcsws(m_target) = surf_file%qcsws(m_file)
3027             ENDIF
3028
3029             IF ( SCAN( TRIM( field_chr ), '%ncs' ) /= 0 )  THEN
3030                IF ( ALLOCATED( surf_target%ncs )  .AND.                       &
3031                     ALLOCATED( surf_file%ncs   ) )                            & 
3032                   surf_target%ncs(m_target) = surf_file%ncs(m_file)
3033             ENDIF
3034
3035             IF ( SCAN( TRIM( field_chr ), '%ncsws' ) /= 0 )  THEN
3036                IF ( ALLOCATED( surf_target%ncsws )  .AND.                     &
3037                     ALLOCATED( surf_file%ncsws   ) )                          & 
3038                   surf_target%ncsws(m_target) = surf_file%ncsws(m_file)
3039             ENDIF
3040
3041             IF ( SCAN( TRIM( field_chr ), '%qrs' ) /= 0 )  THEN
3042                IF ( ALLOCATED( surf_target%qrs )  .AND.                       &
3043                     ALLOCATED( surf_file%qrs   ) )                            & 
3044                  surf_target%qrs(m_target) = surf_file%qrs(m_file)
3045             ENDIF
3046
3047             IF ( SCAN( TRIM( field_chr ), '%qrsws' ) /= 0 )  THEN
3048                IF ( ALLOCATED( surf_target%qrsws )  .AND.                     &
3049                     ALLOCATED( surf_file%qrsws   ) )                          & 
3050                   surf_target%qrsws(m_target) = surf_file%qrsws(m_file)
3051             ENDIF
3052
3053             IF ( SCAN( TRIM( field_chr ), '%nrs' ) /= 0 )  THEN
3054                IF ( ALLOCATED( surf_target%nrs )  .AND.                       &
3055                     ALLOCATED( surf_file%nrs   ) )                            & 
3056                   surf_target%nrs(m_target) = surf_file%nrs(m_file)
3057             ENDIF
3058
3059             IF ( SCAN( TRIM( field_chr ), '%nrsws' ) /= 0 )  THEN
3060                IF ( ALLOCATED( surf_target%nrsws )  .AND.                     &
3061                     ALLOCATED( surf_file%nrsws   ) )                          & 
3062                   surf_target%nrsws(m_target) = surf_file%nrsws(m_file)
3063             ENDIF
3064
3065             IF ( SCAN( TRIM( field_chr ), '%sasws' ) /= 0 )  THEN
3066                IF ( ALLOCATED( surf_target%sasws )  .AND.                     &
3067                     ALLOCATED( surf_file%sasws   ) )                          & 
3068                   surf_target%sasws(m_target) = surf_file%sasws(m_file)
3069             ENDIF
3070
3071             IF ( SCAN( TRIM( field_chr ), '%mom_uv' ) /= 0 )  THEN
3072                IF ( ALLOCATED( surf_target%mom_flux_uv )  .AND.               &
3073                     ALLOCATED( surf_file%mom_flux_uv   ) )                    & 
3074                   surf_target%mom_flux_uv(m_target) =                         &
3075                                           surf_file%mom_flux_uv(m_file)
3076             ENDIF
3077
3078             IF ( SCAN( TRIM( field_chr ), '%mom_w' ) /= 0 )  THEN
3079                IF ( ALLOCATED( surf_target%mom_flux_w )  .AND.                &
3080                     ALLOCATED( surf_file%mom_flux_w   ) )                     & 
3081                   surf_target%mom_flux_w(m_target) =                          &
3082                                           surf_file%mom_flux_w(m_file)
3083             ENDIF
3084
3085             IF ( SCAN( TRIM( field_chr ), '%mom_tke' ) /= 0 )  THEN
3086                IF ( ALLOCATED( surf_target%mom_flux_tke )  .AND.              &
3087                     ALLOCATED( surf_file%mom_flux_tke   ) )                   & 
3088                   surf_target%mom_flux_tke(0:1,m_target) =                    &
3089                                           surf_file%mom_flux_tke(0:1,m_file)
3090             ENDIF
3091
3092          END SUBROUTINE restore_surface_elements
3093
3094    END SUBROUTINE surface_read_restart_data
3095
3096 
3097!------------------------------------------------------------------------------!
3098! Description:
3099! ------------
3100!> Counts the number of surface elements with the same facing, required for
3101!> reading and writing restart data.
3102!------------------------------------------------------------------------------!
3103    SUBROUTINE surface_last_actions
3104
3105       IMPLICIT NONE
3106!
3107!--    Horizontal surfaces
3108       ns_h_on_file(0) = surf_def_h(0)%ns + surf_lsm_h%ns + surf_usm_h%ns
3109       ns_h_on_file(1) = surf_def_h(1)%ns
3110       ns_h_on_file(2) = surf_def_h(2)%ns
3111!
3112!--    Vertical surfaces
3113       ns_v_on_file(0) = surf_def_v(0)%ns + surf_lsm_v(0)%ns + surf_usm_v(0)%ns
3114       ns_v_on_file(1) = surf_def_v(1)%ns + surf_lsm_v(1)%ns + surf_usm_v(1)%ns
3115       ns_v_on_file(2) = surf_def_v(2)%ns + surf_lsm_v(2)%ns + surf_usm_v(2)%ns
3116       ns_v_on_file(3) = surf_def_v(3)%ns + surf_lsm_v(3)%ns + surf_usm_v(3)%ns
3117
3118    END SUBROUTINE surface_last_actions
3119
3120
3121 END MODULE surface_mod
Note: See TracBrowser for help on using the repository browser.