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

Last change on this file since 4746 was 4703, checked in by suehring, 5 years ago

Revise profile and timeseries averaging of land-surface quantities

  • Property svn:keywords set to Id
File size: 280.2 KB
Line 
1!> @file surface_mod.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: surface_mod.f90 4703 2020-09-28 09:21:45Z maronga $
27! Calculate and store total number of surfaces within the model domain.
28!
29! 4694 2020-09-23 15:09:19Z pavelkrc
30! Fix reading of surface data from MPI restart file
31!
32! 4682 2020-09-17 14:13:27Z pavelkrc
33! Fix indexing of horizontal surfaces in write restart for full-3D cases
34!
35! 4671 2020-09-09 20:27:58Z pavelkrc
36! Implementation of downward facing USM and LSM surfaces
37!
38! 4598 2020-07-10 10:13:23Z suehring
39! Revise surface-element mapping in mpi-io restart branch
40!
41! 4595 2020-07-09 17:18:21Z suehring
42! Fix accidently commented subroutine
43!
44! 4594 2020-07-09 15:01:00Z suehring
45! Bugfix, add acc directives for scalar-roughness length
46!
47! 4593 2020-07-09 12:48:18Z suehring
48! Add arrays for pre-calculated ln(z/z0)
49!
50! 4586 2020-07-01 16:16:43Z gronemeier
51! renamed Richardson flux number into gradient Richardson number (1D model)
52!
53! 4559 2020-06-11 08:51:48Z raasch
54! File re-formatted to follow the PALM coding standard
55!
56! 4535 2020-05-15 12:07:23Z raasch
57! Bugfix for restart data format query
58!
59! 4521 2020-05-06 11:39:49Z schwenkel
60! Rename variable
61!
62! 4517 2020-05-03 14:29:30Z raasch
63! Added restart with MPI-IO for reading local arrays
64!
65! 4502 2020-04-17 16:14:16Z schwenkel
66! Implementation of ice microphysics
67!
68! 4495 2020-04-13 20:11:20Z raasch
69! Restart data handling with MPI-IO added
70!
71! 4366 2020-01-09 08:12:43Z raasch
72! Workaround implemented to avoid vectorization bug on NEC Aurora
73!
74! 4360 2020-01-07 11:25:50Z suehring
75! Fix also remaining message calls.
76!
77! 4354 2019-12-19 16:10:18Z suehring
78! Bugfix in message call and specify error number
79!
80! 4346 2019-12-18 11:55:56Z motisi
81! Introduction of wall_flags_total_0, which currently sets bits based on static topography
82! information used in wall_flags_static_0
83!
84! 4331 2019-12-10 18:25:02Z suehring
85! -pt_2m - array is moved to diagnostic_output_quantities
86!
87! 4329 2019-12-10 15:46:36Z motisi
88! Renamed wall_flags_0 to wall_flags_static_0
89!
90! 4245 2019-09-30 08:40:37Z pavelkrc
91! Corrected "Former revisions" section
92!
93! 4168 2019-08-16 13:50:17Z suehring
94! Remove functions get_topography_top_index. These are now replaced by precalculated arrays because
95! of too much CPU-time consumption
96!
97! 4159 2019-08-15 13:31:35Z suehring
98! Surface classification revised and adjusted to changes in init_grid
99!
100! 4156 2019-08-14 09:18:14Z schwenkel
101! Bugfix in case of cloud microphysics morrison
102!
103! 4150 2019-08-08 20:00:47Z suehring
104! Generic routine to initialize single surface properties added
105!
106! 4104 2019-07-17 17:08:20Z suehring
107! Bugfix, initialization of index space for boundary data structure accidantly run over ghost
108! points, causing a segmentation fault.
109!
110! 3943 2019-05-02 09:50:41Z maronga
111! - Revise initialization of the boundary data structure
112! - Add new data structure to set boundary conditions at vertical walls
113!
114! 3943 2019-05-02 09:50:41Z maronga
115! Removed qsws_eb as it is no longer needed.
116!
117! 3933 2019-04-25 12:33:20Z kanani
118! Add (de)allocation of pt_2m,
119! Bugfix: initialize pt_2m
120!
121! 3833 2019-03-28 15:04:04Z forkel
122! Added USE chem_gasphase_mod (chem_modules will not transport nvar and nspec anymore)
123!
124! 3772 2019-02-28 15:51:57Z suehring
125! Small change in the todo's
126!
127! 3767 2019-02-27 08:18:02Z raasch
128! Unused variables removed from rrd-subroutine parameter list
129!
130! 3761 2019-02-25 15:31:42Z raasch
131! OpenACC directives added to avoid compiler warnings about unused variables, unused variable
132! removed
133!
134! 3745 2019-02-15 18:57:56Z suehring
135! +waste_heat
136!
137! 3744 2019-02-15 18:38:58Z suehring
138! OpenACC port for SPEC
139!
140! 2233 2017-05-30 18:08:54Z suehring
141! Initial revision
142!
143!
144! Description:
145! ------------
146!> Surface module defines derived data structures to treat surface-bounded grid cells. Three
147!> different types of surfaces are defined: default surfaces, natural surfaces, and urban surfaces.
148!> The module encompasses the allocation and initialization of surface arrays, and handles reading
149!> and writing restart data. In addition, a further derived data structure is defined, in order to
150!> set boundary conditions at surfaces.
151!> @todo For the moment, downward-facing surfaces are only classified as default type
152!> @todo Clean up urban-surface variables (some of them are not used any more)
153!> @todo Revise initialization of surface fluxes (especially for chemistry)
154!> @todo Get rid-off deallocation routines in restarts
155!--------------------------------------------------------------------------------------------------!
156 MODULE surface_mod
157
158    USE arrays_3d,                                                                                 &
159        ONLY:  heatflux_input_conversion,                                                          &
160               momentumflux_input_conversion,                                                      &
161               rho_air,                                                                            &
162               rho_air_zw,                                                                         &
163               zu,                                                                                 &
164               zw,                                                                                 &
165               waterflux_input_conversion
166
167    USE chem_gasphase_mod,                                                                         &
168        ONLY:  nvar,                                                                               &
169               spc_names
170
171    USE chem_modules
172
173    USE control_parameters
174
175    USE indices,                                                                                   &
176        ONLY:  nxl,                                                                                &
177               nxlg,                                                                               &
178               nxr,                                                                                &
179               nxrg,                                                                               &
180               nys,                                                                                &
181               nysg,                                                                               &
182               nyn,                                                                                &
183               nyng,                                                                               &
184               nzb,                                                                                &
185               nzt,                                                                                &
186               wall_flags_total_0
187
188    USE grid_variables,                                                                            &
189        ONLY:  dx,                                                                                 &
190               dy
191
192    USE kinds
193
194    USE model_1d_mod,                                                                              &
195        ONLY:  ri1d,                                                                               &
196               us1d,                                                                               &
197               usws1d,                                                                             &
198               vsws1d
199
200    USE restart_data_mpi_io_mod,                                                                   &
201        ONLY:  rd_mpi_io_surface_filetypes,                                                        &
202               rrd_mpi_io,                                                                         &
203               rrd_mpi_io_global_array,                                                            &
204               rrd_mpi_io_surface,                                                                 &
205               total_number_of_surface_values,                                                     &
206               wrd_mpi_io,                                                                         &
207               wrd_mpi_io_global_array,                                                            &
208               wrd_mpi_io_surface
209
210    IMPLICIT NONE
211
212!
213!-- Data type used to identify grid-points where horizontal boundary conditions are applied
214    TYPE bc_type
215       INTEGER(iwp) ::  ioff  !< offset value in x-direction, used to determine index of surface element
216       INTEGER(iwp) ::  joff  !< offset value in y-direction, used to determine index of surface element
217       INTEGER(iwp) ::  koff  !< offset value in z-direction, used to determine index of surface element
218       INTEGER(iwp) ::  ns    !< number of surface elements on the PE
219
220       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i  !< x-index linking to the PALM 3D-grid
221       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j  !< y-index linking to the PALM 3D-grid
222       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k  !< z-index linking to the PALM 3D-grid
223
224       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  end_index    !< end index within surface data type for given (j,i)
225       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  start_index  !< start index within surface data type for given (j,i)
226
227    END TYPE bc_type
228!
229!-- Data type used to identify and treat surface-bounded grid points
230    TYPE surf_type
231
232       INTEGER(iwp) ::  ioff        !< offset value in x-direction, used to determine index of surface element
233       INTEGER(iwp) ::  joff        !< offset value in y-direction, used to determine index of surface element
234       INTEGER(iwp) ::  koff        !< offset value in z-direction, used to determine index of surface element
235       INTEGER(iwp) ::  ns          !< number of surface elements on the PE
236       INTEGER(iwp) ::  ns_tot = 0  !< number of surface elements within the entire model domain
237
238       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i  !< x-index linking to the PALM 3D-grid
239       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j  !< y-index linking to the PALM 3D-grid
240       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k  !< z-index linking to the PALM 3D-grid
241
242       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  facing  !< Bit indicating surface orientation
243
244       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  start_index  !< Start index within surface data type for given (j,i)
245       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  end_index    !< End index within surface data type for given (j,i)
246
247       LOGICAL ::  albedo_from_ascii = .FALSE. !< flag indicating that albedo for urban surfaces is input via ASCII format
248                                               !< (just for a workaround)
249
250       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z_mo     !< surface-layer height
251       REAL(wp), DIMENSION(:), ALLOCATABLE ::  uvw_abs  !< absolute surface-parallel velocity
252       REAL(wp), DIMENSION(:), ALLOCATABLE ::  us       !< friction velocity
253       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ts       !< scaling parameter temerature
254       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qs       !< scaling parameter humidity
255       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ss       !< scaling parameter passive scalar
256       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qcs      !< scaling parameter qc
257       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ncs      !< scaling parameter nc
258       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qis      !< scaling parameter qi
259       REAL(wp), DIMENSION(:), ALLOCATABLE ::  nis      !< scaling parameter ni
260       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qrs      !< scaling parameter qr
261       REAL(wp), DIMENSION(:), ALLOCATABLE ::  nrs      !< scaling parameter nr
262
263       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ol       !< Obukhov length
264       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rib      !< Richardson bulk number
265
266       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0       !< roughness length for momentum
267       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0h      !< roughness length for heat
268       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z0q      !< roughness length for humidity
269
270       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt1      !< potential temperature at first grid level
271       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qv1      !< mixing ratio at first grid level
272       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vpt1     !< virtual potential temperature at first grid level
273
274       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  css    !< scaling parameter chemical species
275!
276!--    Pre-defined arrays for ln(z/z0)
277       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ln_z_z0  !< ln(z/z0)
278       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ln_z_z0h !< ln(z/z0h)
279       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ln_z_z0q !< ln(z/z0q)
280!
281!--    Define arrays for surface fluxes
282       REAL(wp), DIMENSION(:), ALLOCATABLE ::  usws     !< vertical momentum flux for u-component at horizontal surfaces
283       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vsws     !< vertical momentum flux for v-component at horizontal surfaces
284
285       REAL(wp), DIMENSION(:), ALLOCATABLE ::  shf      !< surface flux sensible heat
286       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws     !< surface flux latent heat
287       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ssws     !< surface flux passive scalar
288       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qcsws    !< surface flux qc
289       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ncsws    !< surface flux nc
290       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qisws    !< surface flux qi
291       REAL(wp), DIMENSION(:), ALLOCATABLE ::  nisws    !< surface flux ni
292       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qrsws    !< surface flux qr
293       REAL(wp), DIMENSION(:), ALLOCATABLE ::  nrsws    !< surface flux nr
294       REAL(wp), DIMENSION(:), ALLOCATABLE ::  sasws    !< surface flux salinity
295!--    Added for SALSA:
296       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  answs  !< surface flux aerosol number: dim 1: flux, dim 2: bin
297       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  amsws  !< surface flux aerosol mass:   dim 1: flux, dim 2: bin
298       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gtsws  !< surface flux gesous tracers: dim 1: flux, dim 2: gas
299
300       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  cssws  !< surface flux chemical species
301!
302!--    Required for horizontal walls in production_e
303       REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_0  !< virtual velocity component (see production_e_init for further explanation)
304       REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_0  !< virtual velocity component (see production_e_init for further explanation)
305
306       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  mom_flux_uv   !< momentum flux usvs and vsus at vertical surfaces
307                                                               !< (used in diffusion_u and diffusion_v)
308       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  mom_flux_w    !< momentum flux wsus and wsvs at vertical surfaces
309                                                               !< (used in diffusion_w)
310       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  mom_flux_tke  !< momentum flux usvs, vsus, wsus, wsvs at vertical surfaces at grid
311                                                               !< center (used in production_e)
312!
313!--    Variables required for LSM as well as for USM
314       CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE ::  building_type_name    !< building type name at surface element
315       CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE ::  pavement_type_name    !< pavement type name at surface element
316       CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE ::  vegetation_type_name  !< water type at name surface element
317       CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE ::  water_type_name       !< water type at name surface element
318
319       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nzt_pavement     !< top index for pavement in soil
320       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  building_type    !< building type at surface element
321       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  pavement_type    !< pavement type at surface element
322       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  vegetation_type  !< vegetation type at surface element
323       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  water_type       !< water type at surface element
324
325       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  albedo_type  !< albedo type, for each fraction
326                                                                  !< (wall,green,window or vegetation,pavement water)
327
328       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  building_surface  !< flag parameter indicating that the surface element is covered
329                                                                 !< by buildings (no LSM actions, not implemented yet)
330       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  building_covered  !< flag indicating that buildings are on top of orography,
331                                                                 !< only used for vertical surfaces in LSM
332       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  pavement_surface    !< flag parameter for pavements
333       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  water_surface       !< flag parameter for water surfaces
334       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  vegetation_surface  !< flag parameter for natural land surfaces
335
336       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  albedo  !< broadband albedo for each surface fraction
337                                                         !< (LSM: vegetation, water, pavement; USM: wall, green, window)
338       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  emissivity  !< emissivity of the surface, for each fraction
339                                                             !< (LSM: vegetation, water, pavement; USM: wall, green, window)
340       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  frac  !< relative surface fraction
341                                                       !< (LSM: vegetation, water, pavement; USM: wall, green, window)
342
343       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  aldif       !< albedo for longwave diffusive radiation, solar angle of 60 degrees
344       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  aldir       !< albedo for longwave direct radiation, solar angle of 60 degrees
345       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  asdif       !< albedo for shortwave diffusive radiation, solar angle of 60 deg.
346       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  asdir       !< albedo for shortwave direct radiation, solar angle of 60 degrees
347       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  rrtm_aldif  !< albedo for longwave diffusive radiation, solar angle of 60 degrees
348       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  rrtm_aldir  !< albedo for longwave direct radiation, solar angle of 60 degrees
349       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  rrtm_asdif  !< albedo for shortwave diffusive radiation, solar angle of 60 deg.
350       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  rrtm_asdir  !< albedo for shortwave direct radiation, solar angle of 60 degrees
351
352       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  q_surface        !< skin-surface mixing ratio
353       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  pt_surface       !< skin-surface temperature
354       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  vpt_surface      !< skin-surface virtual temperature
355       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  rad_net          !< net radiation
356       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  rad_net_l        !< net radiation, used in USM
357       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_h         !< heat conductivity of soil/ wall (W/m/K)
358       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_h_green   !< heat conductivity of green soil (W/m/K)
359       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_h_window  !< heat conductivity of windows (W/m/K)
360       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_h_def     !< default heat conductivity of soil (W/m/K)
361
362       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_lw_in   !< incoming longwave radiation
363       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_lw_out  !< emitted longwave radiation
364       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_lw_dif  !< incoming longwave radiation from sky
365       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_lw_ref  !< incoming longwave radiation from reflection
366       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_lw_res  !< resedual longwave radiation in surface after last reflection step
367       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_sw_in   !< incoming shortwave radiation
368       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_sw_out  !< emitted shortwave radiation
369       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_sw_dir  !< direct incoming shortwave radiation
370       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_sw_dif  !< diffuse incoming shortwave radiation
371       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_sw_ref  !< incoming shortwave radiation from reflection
372       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_sw_res  !< resedual shortwave radiation in surface after last reflection step
373
374       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_liq             !< liquid water coverage (of vegetated area)
375       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_veg             !< vegetation coverage
376       REAL(wp), DIMENSION(:), ALLOCATABLE ::  f_sw_in           !< fraction of absorbed shortwave radiation by the surface layer
377                                                                 !< (not implemented yet)
378       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ghf               !< ground heat flux
379       REAL(wp), DIMENSION(:), ALLOCATABLE ::  g_d               !< coefficient for dependence of r_canopy
380                                                                 !< on water vapour pressure deficit
381       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lai               !< leaf area index
382       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surface_u  !< coupling between surface and soil (depends on vegetation type)
383                                                                 !< (W/m2/K)
384       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surface_s  !< coupling between surface and soil (depends on vegetation type)
385                                                                 !< (W/m2/K)
386       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_liq          !< surface flux of latent heat (liquid water portion)
387       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_soil         !< surface flux of latent heat (soil portion)
388       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_veg          !< surface flux of latent heat (vegetation portion)
389
390       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_a           !< aerodynamic resistance
391       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_a_green     !< aerodynamic resistance at green fraction
392       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_a_window    !< aerodynamic resistance at window fraction
393       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_canopy      !< canopy resistance
394       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_soil        !< soil resistance
395       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_soil_min    !< minimum soil resistance
396       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_s           !< total surface resistance (combination of r_soil and r_canopy)
397       REAL(wp), DIMENSION(:), ALLOCATABLE ::  r_canopy_min  !< minimum canopy (stomatal) resistance
398
399       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_10cm  !< near surface air potential temperature at distance 10 cm from
400                                                        !< the surface (K)
401
402       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  alpha_vg         !< coef. of Van Genuchten
403       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_w         !< hydraulic diffusivity of soil (?)
404       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gamma_w          !< hydraulic conductivity of soil (W/m/K)
405       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gamma_w_sat      !< hydraulic conductivity at saturation
406       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  l_vg             !< coef. of Van Genuchten
407       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_fc             !< soil moisture at field capacity (m3/m3)
408       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_res            !< residual soil moisture
409       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_sat            !< saturation soil moisture (m3/m3)
410       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  m_wilt           !< soil moisture at permanent wilting point (m3/m3)
411       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_vg             !< coef. Van Genuchten
412       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_total_def  !< default volumetric heat capacity of the (soil) layer (J/m3/K)
413       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_total      !< volumetric heat capacity of the actual soil matrix (J/m3/K)
414       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  root_fr          !< root fraction within the soil layers
415
416!--    Indoor model variables
417       REAL(wp), DIMENSION(:), ALLOCATABLE ::  waste_heat  !< waste heat
418!
419!--    Urban surface variables
420       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  surface_types  !< array of types of wall parameters
421
422       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  isroof_surf   !< flag indicating roof surfaces
423       LOGICAL, DIMENSION(:), ALLOCATABLE  ::  ground_level  !< flag indicating ground floor level surfaces
424
425       REAL(wp), DIMENSION(:), ALLOCATABLE ::  target_temp_summer  !< indoor target temperature summer
426       REAL(wp), DIMENSION(:), ALLOCATABLE ::  target_temp_winter  !< indoor target temperature summer
427
428       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_surface           !< heat capacity of the wall surface skin (J/m2/K)
429       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_surface_green     !< heat capacity of the green surface skin (J/m2/K)
430       REAL(wp), DIMENSION(:), ALLOCATABLE ::  c_surface_window    !< heat capacity of the window surface skin (J/m2/K)
431       REAL(wp), DIMENSION(:), ALLOCATABLE ::  green_type_roof     !< type of the green roof
432       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surf         !< heat conductivity between air and surface (W/m2/K)
433       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surf_green   !< heat conductivity between air and green surface (W/m2/K)
434       REAL(wp), DIMENSION(:), ALLOCATABLE ::  lambda_surf_window  !< heat conductivity between air and window surface (W/m2/K)
435       REAL(wp), DIMENSION(:), ALLOCATABLE ::  thickness_wall      !< thickness of the wall, roof and soil layers
436       REAL(wp), DIMENSION(:), ALLOCATABLE ::  thickness_green     !< thickness of the green wall, roof and soil layers
437       REAL(wp), DIMENSION(:), ALLOCATABLE ::  thickness_window    !< thickness of the window wall, roof and soil layers
438       REAL(wp), DIMENSION(:), ALLOCATABLE ::  transmissivity      !< transmissivity of windows
439
440       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutsl  !< reflected shortwave radiation for local surface in i-th reflection
441       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutll  !< reflected + emitted longwave radiation for local surface
442                                                          !< in i-th reflection
443       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfhf     !< total radiation flux incoming to minus outgoing from local surface
444
445       REAL(wp), DIMENSION(:), ALLOCATABLE ::  tt_surface_wall_m    !< surface temperature tendency (K)
446       REAL(wp), DIMENSION(:), ALLOCATABLE ::  tt_surface_window_m  !< window surface temperature tendency (K)
447       REAL(wp), DIMENSION(:), ALLOCATABLE ::  tt_surface_green_m   !< green surface temperature tendency (K)
448       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wshf                 !< kinematic wall heat flux of sensible heat
449                                                                    !< (actually no longer needed)
450       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wshf_eb              !< wall heat flux of sensible heat in wall normal direction
451
452       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb          !< wall ground heat flux
453       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb_window   !< window ground heat flux
454       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb_green    !< green ground heat flux
455       REAL(wp), DIMENSION(:), ALLOCATABLE ::  iwghf_eb         !< indoor wall ground heat flux
456       REAL(wp), DIMENSION(:), ALLOCATABLE ::  iwghf_eb_window  !< indoor window ground heat flux
457
458       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_lw_out_change_0  !<
459
460       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinsw   !< shortwave radiation falling to local surface including radiation
461                                                          !< from reflections
462       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutsw  !< total shortwave radiation outgoing from nonvirtual surfaces surfaces
463                                                          !< after all reflection
464       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlw   !< longwave radiation falling to local surface including radiation from
465                                                          !< reflections
466       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutlw  !< total longwave radiation outgoing from nonvirtual surfaces surfaces
467                                                          !< after all reflection
468
469       REAL(wp), DIMENSION(:), ALLOCATABLE ::  n_vg_green      !< vangenuchten parameters
470       REAL(wp), DIMENSION(:), ALLOCATABLE ::  alpha_vg_green  !< vangenuchten parameters
471       REAL(wp), DIMENSION(:), ALLOCATABLE ::  l_vg_green      !< vangenuchten parameters
472
473
474       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_wall         !< volumetric heat capacity of the material ( J m-3 K-1 )
475                                                                    !< (= 2.19E6)
476       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_wall            !< wall grid spacing (center-center)
477       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_wall           !< 1/dz_wall
478       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_wall_stag       !< wall grid spacing (edge-edge)
479       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_wall_stag      !< 1/dz_wall_stag
480       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tt_wall_m          !< t_wall prognostic array
481       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw                 !< wall layer depths (m)
482       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_window       !< volumetric heat capacity of the window material ( J m-3 K-1 )
483                                                                    !< (= 2.19E6)
484       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_window          !< window grid spacing (center-center)
485       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_window         !< 1/dz_window
486       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_window_stag     !< window grid spacing (edge-edge)
487       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_window_stag    !< 1/dz_window_stag
488       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tt_window_m        !< t_window prognostic array
489       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw_window          !< window layer depths (m)
490       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_green        !< volumetric heat capacity of the green material ( J m-3 K-1 )
491                                                                    !< (= 2.19E6)
492       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  rho_c_total_green  !< volumetric heat capacity of the moist green material
493                                                                    !< ( J m-3 K-1 ) (= 2.19E6)
494       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_green           !< green grid spacing (center-center)
495       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_green          !< 1/dz_green
496       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  dz_green_stag      !< green grid spacing (edge-edge)
497       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ddz_green_stag     !< 1/dz_green_stag
498       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tt_green_m         !< t_green prognostic array
499       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw_green           !< green layer depths (m)
500
501       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gamma_w_green_sat  !< hydraulic conductivity
502       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  lambda_w_green     !<
503       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  gamma_w_green      !< hydraulic conductivity
504       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tswc_h_m           !<
505
506!
507!--    Arrays for time averages
508       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_net_av          !< average of rad_net_l
509       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinsw_av         !< average of sw radiation falling to local surface including
510                                                                   !< radiation from reflections
511       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlw_av         !< average of lw radiation falling to local surface including
512                                                                   !< radiation from reflections
513       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinswdir_av      !< average of direct sw radiation falling to local surface
514       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinswdif_av      !< average of diffuse sw radiation from sky and model boundary
515                                                                   !< falling to local surface
516       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlwdif_av      !< average of diffuse lw radiation from sky and model boundary
517                                                                   !< falling to local surface
518       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinswref_av      !< average of sw radiation falling to surface from reflections
519       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinlwref_av      !< average of lw radiation falling to surface from reflections
520       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutsw_av        !< average of total sw radiation outgoing from nonvirtual
521                                                                   !< surfaces surfaces after all reflection
522       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfoutlw_av        !< average of total lw radiation outgoing from nonvirtual
523                                                                   !< surfaces after all reflection
524       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfins_av          !< average of array of residua of sw radiation absorbed in
525                                                                   !< surface after last reflection
526       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinl_av          !< average of array of residua of lw radiation absorbed in
527                                                                   !< surface after last reflection
528       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfhf_av           !< average of total radiation flux incoming to minus outgoing
529                                                                   !< from local surface
530       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb_av          !< average of wghf_eb
531       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb_window_av   !< average of wghf_eb window
532       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wghf_eb_green_av    !< average of wghf_eb window
533       REAL(wp), DIMENSION(:), ALLOCATABLE ::  iwghf_eb_av         !< indoor average of wghf_eb
534       REAL(wp), DIMENSION(:), ALLOCATABLE ::  iwghf_eb_window_av  !< indoor average of wghf_eb window
535       REAL(wp), DIMENSION(:), ALLOCATABLE ::  wshf_eb_av          !< average of wshf_eb
536       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_av             !< average of qsws
537       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_veg_av         !< average of qsws_veg_eb
538       REAL(wp), DIMENSION(:), ALLOCATABLE ::  qsws_liq_av         !< average of qsws_liq_eb
539       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_surf_wall_av      !< average of wall surface temperature (K)
540       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_surf_av           !< average of wall surface temperature (K)
541       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_surf_window_av    !< average of window surface temperature (K)
542       REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_surf_green_av     !< average of green wall surface temperature (K)
543
544       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_10cm_av  !< average of theta_10cm (K)
545
546       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  t_wall_av    !< Average of t_wall
547       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  t_window_av  !< Average of t_window
548       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  t_green_av   !< Average of t_green
549       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  swc_av       !< Average of swc
550
551    END TYPE surf_type
552
553    TYPE (bc_type), DIMENSION(0:1)  ::  bc_h  !< boundary condition data type, horizontal upward- and downward facing surfaces
554    TYPE (bc_type), DIMENSION(0:3)  ::  bc_v  !< boundary condition data type, vertical surfaces
555
556    TYPE (surf_type), DIMENSION(0:2), TARGET ::  surf_def_h  !< horizontal default surfaces (Up, Down, and Top)
557    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_def_v  !< vertical default surfaces (North, South, East, West)
558    TYPE (surf_type), DIMENSION(0:1), TARGET ::  surf_lsm_h  !< horizontal natural land surfaces (Up, Down)
559    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_lsm_v  !< vertical land surfaces (North, South, East, West)
560    TYPE (surf_type), DIMENSION(0:1), TARGET ::  surf_usm_h  !< horizontal urban surfaces (Up, Down)
561    TYPE (surf_type), DIMENSION(0:3), TARGET ::  surf_usm_v  !< vertical urban surfaces (North, South, East, West)
562
563    INTEGER(iwp), PARAMETER ::  ind_veg_wall  = 0  !< index for vegetation / wall-surface fraction, used for access of albedo,
564                                                   !< emissivity, etc., for each surface type
565    INTEGER(iwp), PARAMETER ::  ind_pav_green = 1  !< index for pavement / green-wall surface fraction, used for access of albedo,
566                                                   !< emissivity, etc., for each surface type
567    INTEGER(iwp), PARAMETER ::  ind_wat_win   = 2  !< index for water / window-surface fraction, used for access of albedo,
568                                                   !< emissivity, etc., for each surface type
569
570    INTEGER(iwp) ::  ns_h_on_file(0:2)  !< total number of horizontal surfaces with the same facing, required for writing
571                                        !< restart data
572    INTEGER(iwp) ::  ns_v_on_file(0:3)  !< total number of vertical surfaces with the same facing, required for writing restart data
573
574    LOGICAL ::  vertical_surfaces_exist     = .FALSE.  !< flag indicating that there are vertical urban/land surfaces
575                                                       !< in the domain (required to activiate RTM)
576
577    LOGICAL ::  surf_bulk_cloud_model       = .FALSE.  !< use cloud microphysics
578    LOGICAL ::  surf_microphysics_morrison  = .FALSE.  !< use 2-moment Morrison (add. prog. eq. for nc and qc)
579    LOGICAL ::  surf_microphysics_seifert   = .FALSE.  !< use 2-moment Seifert and Beheng scheme
580    LOGICAL ::  surf_microphysics_ice_phase = .FALSE.  !< use 2-moment Seifert and Beheng scheme
581
582
583    SAVE
584
585    PRIVATE
586
587    INTERFACE init_bc
588       MODULE PROCEDURE init_bc
589    END INTERFACE init_bc
590
591    INTERFACE init_single_surface_properties
592       MODULE PROCEDURE init_single_surface_properties
593    END INTERFACE init_single_surface_properties
594
595    INTERFACE init_surfaces
596       MODULE PROCEDURE init_surfaces
597    END INTERFACE init_surfaces
598
599    INTERFACE init_surface_arrays
600       MODULE PROCEDURE init_surface_arrays
601    END INTERFACE init_surface_arrays
602
603    INTERFACE surface_rrd_local
604       MODULE PROCEDURE surface_rrd_local_ftn
605       MODULE PROCEDURE surface_rrd_local_mpi
606    END INTERFACE surface_rrd_local
607
608    INTERFACE surface_wrd_local
609       MODULE PROCEDURE surface_wrd_local
610    END INTERFACE surface_wrd_local
611
612    INTERFACE surface_last_actions
613       MODULE PROCEDURE surface_last_actions
614    END INTERFACE surface_last_actions
615
616    INTERFACE surface_restore_elements
617       MODULE PROCEDURE surface_restore_elements_1d
618       MODULE PROCEDURE surface_restore_elements_2d
619    END INTERFACE surface_restore_elements
620
621#if defined( _OPENACC )
622    INTERFACE enter_surface_arrays
623       MODULE PROCEDURE enter_surface_arrays
624    END INTERFACE
625
626    INTERFACE exit_surface_arrays
627       MODULE PROCEDURE exit_surface_arrays
628    END INTERFACE
629#endif
630
631!
632!-- Public variables
633    PUBLIC bc_h,                                                                                   &
634           bc_v,                                                                                   &
635           ind_pav_green,                                                                          &
636           ind_veg_wall,                                                                           &
637           ind_wat_win,                                                                            &
638           ns_h_on_file,                                                                           &
639           ns_v_on_file,                                                                           &
640           surf_def_h,                                                                             &
641           surf_def_v,                                                                             &
642           surf_lsm_h,                                                                             &
643           surf_lsm_v,                                                                             &
644           surf_usm_h,                                                                             &
645           surf_usm_v,                                                                             &
646           surf_type,                                                                              &
647           vertical_surfaces_exist,                                                                &
648           surf_bulk_cloud_model,                                                                  &
649           surf_microphysics_morrison,                                                             &
650           surf_microphysics_seifert,                                                              &
651           surf_microphysics_ice_phase
652!
653!-- Public subroutines and functions
654    PUBLIC init_bc,                                                                                &
655           init_single_surface_properties,                                                         &
656           init_surfaces,                                                                          &
657           init_surface_arrays,                                                                    &
658           surface_last_actions,                                                                   &
659           surface_rrd_local,                                                                      &
660           surface_restore_elements,                                                               &
661           surface_wrd_local
662
663#if defined( _OPENACC )
664    PUBLIC enter_surface_arrays,                                                                   &
665           exit_surface_arrays
666#endif
667
668 CONTAINS
669
670!--------------------------------------------------------------------------------------------------!
671! Description:
672! ------------
673!> Initialize data type for setting boundary conditions at horizontal and vertical surfaces.
674!--------------------------------------------------------------------------------------------------!
675 SUBROUTINE init_bc
676
677    IMPLICIT NONE
678
679    INTEGER(iwp) ::  i  !< loop index along x-direction
680    INTEGER(iwp) ::  j  !< loop index along y-direction
681    INTEGER(iwp) ::  k  !< loop index along y-direction
682    INTEGER(iwp) ::  l  !< running index for differently aligned surfaces
683
684    INTEGER(iwp), DIMENSION(0:1) ::  num_h          !< number of horizontal surfaces on subdomain
685    INTEGER(iwp), DIMENSION(0:1) ::  num_h_kji      !< number of horizontal surfaces at (j,i)-grid point
686    INTEGER(iwp), DIMENSION(0:1) ::  start_index_h  !< local start index of horizontal surface elements
687
688    INTEGER(iwp), DIMENSION(0:3) ::  num_v          !< number of vertical surfaces on subdomain
689    INTEGER(iwp), DIMENSION(0:3) ::  num_v_kji      !< number of vertical surfaces at (j,i)-grid point
690    INTEGER(iwp), DIMENSION(0:3) ::  start_index_v  !< local start index of vertical surface elements
691!
692!-- Set offset indices, i.e. index difference between surface element and surface-bounded grid point.
693!-- Horizontal surfaces - no horizontal offsets
694    bc_h(:)%ioff = 0
695    bc_h(:)%joff = 0
696!
697!-- Horizontal surfaces, upward facing (0) and downward facing (1)
698    bc_h(0)%koff = -1
699    bc_h(1)%koff = 1
700!
701!-- Vertical surfaces - no vertical offset
702    bc_v(0:3)%koff = 0
703!
704!-- North- and southward facing - no offset in x
705    bc_v(0:1)%ioff = 0
706!
707!-- Northward facing offset in y
708    bc_v(0)%joff = -1
709!
710!-- Southward facing offset in y
711    bc_v(1)%joff = 1
712!
713!-- East- and westward facing - no offset in y
714    bc_v(2:3)%joff = 0
715!
716!-- Eastward facing offset in x
717    bc_v(2)%ioff = -1
718!
719!-- Westward facing offset in y
720    bc_v(3)%ioff = 1
721!
722!-- Initialize data structure for horizontal surfaces, i.e. count the number of surface elements,
723!-- allocate and initialize the respective index arrays, and set the respective start and end
724!-- indices at each (j,i)-location. The index space is defined also over the ghost points, so that
725!-- e.g. boundary conditions for diagnostic quanitities can be set on ghost points so that no
726!-- exchange is required any more.
727    DO  l = 0, 1
728!
729!--    Count the number of upward- and downward-facing surfaces on subdomain
730       num_h(l) = 0
731       DO  i = nxlg, nxrg
732          DO  j = nysg, nyng
733             DO  k = nzb+1, nzt
734!
735!--             Check if current gridpoint belongs to the atmosphere
736                IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
737                   IF ( .NOT. BTEST( wall_flags_total_0(k+bc_h(l)%koff, j+bc_h(l)%joff,            &
738                                     i+bc_h(l)%ioff), 0 ) )  num_h(l) = num_h(l) + 1
739                ENDIF
740             ENDDO
741          ENDDO
742       ENDDO
743!
744!--    Save the number of horizontal surface elements
745       bc_h(l)%ns = num_h(l)
746!
747!--    ALLOCATE arrays for horizontal surfaces
748       ALLOCATE( bc_h(l)%i(1:bc_h(l)%ns) )
749       ALLOCATE( bc_h(l)%j(1:bc_h(l)%ns) )
750       ALLOCATE( bc_h(l)%k(1:bc_h(l)%ns) )
751       ALLOCATE( bc_h(l)%start_index(nysg:nyng,nxlg:nxrg) )
752       ALLOCATE( bc_h(l)%end_index(nysg:nyng,nxlg:nxrg) )
753       bc_h(l)%start_index = 1
754       bc_h(l)%end_index   = 0
755
756       num_h(l)         = 1
757       start_index_h(l) = 1
758       DO  i = nxlg, nxrg
759          DO  j = nysg, nyng
760
761             num_h_kji(l) = 0
762             DO  k = nzb+1, nzt
763!
764!--             Check if current gridpoint belongs to the atmosphere
765                IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
766!
767!--                Upward-facing
768                   IF ( .NOT. BTEST( wall_flags_total_0(k+bc_h(l)%koff, j+bc_h(l)%joff,            &
769                                     i+bc_h(l)%ioff), 0 ) )  THEN
770                      bc_h(l)%i(num_h(l)) = i
771                      bc_h(l)%j(num_h(l)) = j
772                      bc_h(l)%k(num_h(l)) = k
773                      num_h_kji(l)        = num_h_kji(l) + 1
774                      num_h(l)            = num_h(l) + 1
775                   ENDIF
776                ENDIF
777             ENDDO
778             bc_h(l)%start_index(j,i) = start_index_h(l)
779             bc_h(l)%end_index(j,i)   = bc_h(l)%start_index(j,i) + num_h_kji(l) - 1
780             start_index_h(l)         = bc_h(l)%end_index(j,i) + 1
781          ENDDO
782       ENDDO
783    ENDDO
784
785!
786!-- Initialize data structure for vertical surfaces, i.e. count the number of surface elements,
787!-- allocate and initialize the respective index arrays, and set the respective start and end
788!-- indices at each (j,i)-location.
789    DO  l = 0, 3
790!
791!--    Count the number of upward- and downward-facing surfaces on subdomain
792       num_v(l) = 0
793       DO  i = nxl, nxr
794          DO  j = nys, nyn
795             DO  k = nzb+1, nzt
796!
797!--             Check if current gridpoint belongs to the atmosphere
798                IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
799                   IF ( .NOT. BTEST( wall_flags_total_0(k+bc_v(l)%koff, j+bc_v(l)%joff,            &
800                                     i+bc_v(l)%ioff), 0 ) )  num_v(l) = num_v(l) + 1
801                ENDIF
802             ENDDO
803          ENDDO
804       ENDDO
805!
806!--    Save the number of horizontal surface elements
807       bc_v(l)%ns = num_v(l)
808!
809!--    ALLOCATE arrays for horizontal surfaces. In contrast to the horizontal surfaces, the index
810!--    space is not defined over the ghost points.
811       ALLOCATE( bc_v(l)%i(1:bc_v(l)%ns) )
812       ALLOCATE( bc_v(l)%j(1:bc_v(l)%ns) )
813       ALLOCATE( bc_v(l)%k(1:bc_v(l)%ns) )
814       ALLOCATE( bc_v(l)%start_index(nys:nyn,nxl:nxr) )
815       ALLOCATE( bc_v(l)%end_index(nys:nyn,nxl:nxr) )
816       bc_v(l)%start_index = 1
817       bc_v(l)%end_index   = 0
818
819       num_v(l)         = 1
820       start_index_v(l) = 1
821       DO  i = nxl, nxr
822          DO  j = nys, nyn
823
824             num_v_kji(l) = 0
825             DO  k = nzb+1, nzt
826!
827!--             Check if current gridpoint belongs to the atmosphere
828                IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
829!
830!--                Upward-facing
831                   IF ( .NOT. BTEST( wall_flags_total_0(k+bc_v(l)%koff, j+bc_v(l)%joff,            &
832                                     i+bc_v(l)%ioff), 0 ) )  THEN
833                      bc_v(l)%i(num_v(l)) = i
834                      bc_v(l)%j(num_v(l)) = j
835                      bc_v(l)%k(num_v(l)) = k
836                      num_v_kji(l)        = num_v_kji(l) + 1
837                      num_v(l)            = num_v(l) + 1
838                   ENDIF
839                ENDIF
840             ENDDO
841             bc_v(l)%start_index(j,i) = start_index_v(l)
842             bc_v(l)%end_index(j,i)   = bc_v(l)%start_index(j,i) + num_v_kji(l) - 1
843             start_index_v(l)         = bc_v(l)%end_index(j,i) + 1
844          ENDDO
845       ENDDO
846    ENDDO
847
848
849 END SUBROUTINE init_bc
850
851
852!--------------------------------------------------------------------------------------------------!
853! Description:
854! ------------
855!> Initialize horizontal and vertical surfaces. Counts the number of default-, natural and urban
856!> surfaces and allocates memory, respectively.
857!--------------------------------------------------------------------------------------------------!
858 SUBROUTINE init_surface_arrays
859
860
861    USE pegrid
862
863
864    IMPLICIT NONE
865
866    INTEGER(iwp) ::  i         !< running index x-direction
867    INTEGER(iwp) ::  j         !< running index y-direction
868    INTEGER(iwp) ::  k         !< running index z-direction
869    INTEGER(iwp) ::  l         !< index variable for surface facing
870    INTEGER(iwp) ::  kk        !< auxiliary index z-direction
871    INTEGER(iwp) ::  kd        !< direction index
872
873    INTEGER(iwp), DIMENSION(0:2) ::  num_def_h !< number of horizontally-aligned default surfaces
874    INTEGER(iwp), DIMENSION(0:1) ::  num_lsm_h !< number of horizontally-aligned natural surfaces
875    INTEGER(iwp), DIMENSION(0:1) ::  num_usm_h !< number of horizontally-aligned urban surfaces
876    INTEGER(iwp), DIMENSION(0:3) ::  num_def_v !< number of vertically-aligned default surfaces
877    INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v !< number of vertically-aligned natural surfaces
878    INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v !< number of vertically-aligned urban surfaces
879
880    INTEGER(iwp) ::  num_surf_v_l !< number of vertically-aligned local urban/land surfaces
881    INTEGER(iwp) ::  num_surf_v   !< number of vertically-aligned total urban/land surfaces
882
883    LOGICAL ::  building             !< flag indicating building grid point
884    LOGICAL ::  terrain              !< flag indicating natural terrain grid point
885    LOGICAL ::  unresolved_building  !< flag indicating a grid point where actually a building is
886                                     !< defined but not resolved by the vertical grid
887
888    num_def_h = 0
889    num_def_v = 0
890    num_lsm_h = 0
891    num_lsm_v = 0
892    num_usm_h = 0
893    num_usm_v = 0
894!
895!-- Surfaces are classified according to the input data read from static input file. If no input
896!-- file is present, all surfaces are classified either as natural, urban, or default, depending on
897!-- the setting of land_surface and urban_surface. To control this, use the control flag
898!-- topo_no_distinct
899!
900!-- Count number of horizontal surfaces on local domain
901    DO  i = nxl, nxr
902       DO  j = nys, nyn
903          DO  k = nzb+1, nzt
904!
905!--          Check if current gridpoint belongs to the atmosphere
906             IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
907!
908!--             Check if grid point adjoins to any upward- and downward-facing horizontal surface,
909!--             e.g. the Earth surface, plane roofs, or ceilings.
910                DO kk = k-1, k+1, 2
911!
912!--                Check for top-fluxes
913                   IF ( kk == nzt+1  .AND.  use_top_fluxes )  THEN
914                      num_def_h(2) = num_def_h(2) + 1
915                   ELSE
916!
917!--                   set direction index of the potential surface
918                      kd = MERGE( 0, 1, kk == k-1 )
919!
920!--                   test the adjacent grid cell
921                      IF ( .NOT. BTEST( wall_flags_total_0(kk,j,i), 0 ) )  THEN
922!
923!--                      Determine flags indicating a terrain surface, a building surface,
924                         terrain  = BTEST( wall_flags_total_0(kk,j,i), 5 )  .OR.  topo_no_distinct
925                         building = BTEST( wall_flags_total_0(kk,j,i), 6 )  .OR.  topo_no_distinct
926!
927!--                      Unresolved_building indicates a surface with equal height as terrain but with a
928!--                      non-grid resolved building on top. These surfaces will be flagged as urban
929!--                      surfaces.
930                         unresolved_building = BTEST( wall_flags_total_0(kk,j,i), 5 )  .AND.            &
931                                               BTEST( wall_flags_total_0(kk,j,i), 6 )
932!
933!--                      Land-surface type
934                         IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
935                            num_lsm_h(kd)    = num_lsm_h(kd)    + 1
936!
937!--                      Urban surface tpye
938                         ELSEIF ( urban_surface  .AND.  building )  THEN
939                            num_usm_h(kd) = num_usm_h(kd) + 1
940!
941!--                      Default-surface type
942                         ELSEIF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
943                            num_def_h(kd) = num_def_h(kd) + 1
944!
945!--                      Unclassifified surface-grid point. Give error message.
946                         ELSE
947                            WRITE( message_string, * ) 'Unclassified ',                            &
948                                  TRIM(MERGE('  upward','downward',kk==0)),                        &
949                                  '-facing surface element at grid point (k,j,i) = ', k, j, i
950                            CALL message( 'surface_mod', 'PA0698', 1, 2, myid, 6, 0 )
951                         ENDIF
952                      ENDIF
953                   ENDIF
954                ENDDO
955             ENDIF
956          ENDDO
957       ENDDO
958    ENDDO
959!
960!-- Count number of vertical surfaces on local domain
961    DO  i = nxl, nxr
962       DO  j = nys, nyn
963          DO  k = nzb+1, nzt
964             IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
965!
966!--             Northward-facing
967                IF ( .NOT. BTEST( wall_flags_total_0(k,j-1,i), 0 ) )  THEN
968!
969!--                Determine flags indicating terrain or building
970
971                   terrain  = BTEST( wall_flags_total_0(k,j-1,i), 5 )  .OR.  topo_no_distinct
972                   building = BTEST( wall_flags_total_0(k,j-1,i), 6 )  .OR.  topo_no_distinct
973
974                   unresolved_building = BTEST( wall_flags_total_0(k,j-1,i), 5 )  .AND.            &
975                                         BTEST( wall_flags_total_0(k,j-1,i), 6 )
976
977                   IF (  land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
978                      num_lsm_v(0) = num_lsm_v(0) + 1
979                   ELSEIF ( urban_surface  .AND.  building )  THEN
980                      num_usm_v(0) = num_usm_v(0) + 1
981!
982!--                Default-surface type
983                   ELSEIF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
984                      num_def_v(0) = num_def_v(0) + 1
985!
986!--                Unclassifified surface-grid point. Give error message.
987                   ELSE
988                      WRITE( message_string, * ) 'Unclassified northward-facing surface ' //       &
989                                                 'element at grid point (k,j,i) = ', k, j, i
990                      CALL message( 'surface_mod', 'PA0698', 1, 2, myid, 6, 0 )
991
992                   ENDIF
993                ENDIF
994!
995!--             Southward-facing
996                IF ( .NOT. BTEST( wall_flags_total_0(k,j+1,i), 0 ) )  THEN
997!
998!--                Determine flags indicating terrain or building
999                   terrain  = BTEST( wall_flags_total_0(k,j+1,i), 5 )  .OR.  topo_no_distinct
1000                   building = BTEST( wall_flags_total_0(k,j+1,i), 6 )  .OR.  topo_no_distinct
1001
1002                   unresolved_building = BTEST( wall_flags_total_0(k,j+1,i), 5 )  .AND.            &
1003                                         BTEST( wall_flags_total_0(k,j+1,i), 6 )
1004
1005                   IF (  land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
1006                      num_lsm_v(1) = num_lsm_v(1) + 1
1007                   ELSEIF ( urban_surface  .AND.  building )  THEN
1008                      num_usm_v(1) = num_usm_v(1) + 1
1009!
1010!--                Default-surface type
1011                   ELSEIF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
1012                      num_def_v(1) = num_def_v(1) + 1
1013!
1014!--                Unclassifified surface-grid point. Give error message.
1015                   ELSE
1016                      WRITE( message_string, * ) 'Unclassified southward-facing surface ' //       &
1017                                                 'element at grid point (k,j,i) = ', k, j, i
1018                      CALL message( 'surface_mod', 'PA0698', 1, 2, myid, 6, 0 )
1019
1020                   ENDIF
1021                ENDIF
1022!
1023!--             Eastward-facing
1024                IF ( .NOT. BTEST( wall_flags_total_0(k,j,i-1), 0 ) )  THEN
1025!
1026!--                Determine flags indicating terrain or building
1027                   terrain  = BTEST( wall_flags_total_0(k,j,i-1), 5 )  .OR.  topo_no_distinct
1028                   building = BTEST( wall_flags_total_0(k,j,i-1), 6 )  .OR.  topo_no_distinct
1029
1030                   unresolved_building = BTEST( wall_flags_total_0(k,j,i-1), 5 )  .AND.            &
1031                                         BTEST( wall_flags_total_0(k,j,i-1), 6 )
1032
1033                   IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
1034                      num_lsm_v(2) = num_lsm_v(2) + 1
1035                   ELSEIF ( urban_surface  .AND.  building )  THEN
1036                      num_usm_v(2) = num_usm_v(2) + 1
1037!
1038!--                Default-surface type
1039                   ELSEIF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
1040                      num_def_v(2) = num_def_v(2) + 1
1041!
1042!--                Unclassifified surface-grid point. Give error message.
1043                   ELSE
1044                      WRITE( message_string, * ) 'Unclassified eastward-facing surface ' //        &
1045                                                 'element at grid point (k,j,i) = ', k, j, i
1046                      CALL message( 'surface_mod', 'PA0698', 1, 2, myid, 6, 0 )
1047
1048                   ENDIF
1049                ENDIF
1050!
1051!--             Westward-facing
1052                IF ( .NOT. BTEST( wall_flags_total_0(k,j,i+1), 0 ) )  THEN
1053!
1054!--                Determine flags indicating terrain or building
1055                   terrain  = BTEST( wall_flags_total_0(k,j,i+1), 5 )  .OR.  topo_no_distinct
1056                   building = BTEST( wall_flags_total_0(k,j,i+1), 6 )  .OR.  topo_no_distinct
1057
1058                   unresolved_building = BTEST( wall_flags_total_0(k,j,i+1), 5 )  .AND.            &
1059                                         BTEST( wall_flags_total_0(k,j,i+1), 6 )
1060
1061                   IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
1062                      num_lsm_v(3) = num_lsm_v(3) + 1
1063                   ELSEIF ( urban_surface  .AND.  building )  THEN
1064                      num_usm_v(3) = num_usm_v(3) + 1
1065!
1066!--                Default-surface type
1067                   ELSEIF ( .NOT. land_surface  .AND.  .NOT. urban_surface )  THEN
1068                      num_def_v(3) = num_def_v(3) + 1
1069!
1070!--                Unclassifified surface-grid point. Give error message.
1071                   ELSE
1072                      WRITE( message_string, * ) 'Unclassified westward-facing surface ' //        &
1073                                                 'element at grid point (k,j,i) = ', k, j, i
1074                      CALL message( 'surface_mod', 'PA0698', 1, 2, myid, 6, 0 )
1075
1076                   ENDIF
1077                ENDIF
1078             ENDIF
1079          ENDDO
1080       ENDDO
1081    ENDDO
1082
1083!
1084!-- Store number of surfaces per core.
1085!-- Horizontal surface, default type, upward facing
1086    surf_def_h(0)%ns = num_def_h(0)
1087!
1088!-- Horizontal surface, default type, downward facing
1089    surf_def_h(1)%ns = num_def_h(1)
1090!
1091!-- Horizontal surface, default type, top downward facing
1092    surf_def_h(2)%ns = num_def_h(2)
1093!
1094!-- Horizontal surface, natural type, upward facing
1095    surf_lsm_h(0)%ns    = num_lsm_h(0)
1096!
1097!-- Horizontal surface, natural type, downward facing
1098    surf_lsm_h(1)%ns    = num_lsm_h(1)
1099!
1100!-- Horizontal surface, urban type, upward facing
1101    surf_usm_h(0)%ns    = num_usm_h(0)
1102!
1103!-- Horizontal surface, urban type, downward facing
1104    surf_usm_h(1)%ns    = num_usm_h(1)
1105!
1106!-- Vertical surface, default type, northward facing
1107    surf_def_v(0)%ns = num_def_v(0)
1108!
1109!-- Vertical surface, default type, southward facing
1110    surf_def_v(1)%ns = num_def_v(1)
1111!
1112!-- Vertical surface, default type, eastward facing
1113    surf_def_v(2)%ns = num_def_v(2)
1114!
1115!-- Vertical surface, default type, westward facing
1116    surf_def_v(3)%ns = num_def_v(3)
1117!
1118!-- Vertical surface, natural type, northward facing
1119    surf_lsm_v(0)%ns = num_lsm_v(0)
1120!
1121!-- Vertical surface, natural type, southward facing
1122    surf_lsm_v(1)%ns = num_lsm_v(1)
1123!
1124!-- Vertical surface, natural type, eastward facing
1125    surf_lsm_v(2)%ns = num_lsm_v(2)
1126!
1127!-- Vertical surface, natural type, westward facing
1128    surf_lsm_v(3)%ns = num_lsm_v(3)
1129!
1130!-- Vertical surface, urban type, northward facing
1131    surf_usm_v(0)%ns = num_usm_v(0)
1132!
1133!-- Vertical surface, urban type, southward facing
1134    surf_usm_v(1)%ns = num_usm_v(1)
1135!
1136!-- Vertical surface, urban type, eastward facing
1137    surf_usm_v(2)%ns = num_usm_v(2)
1138!
1139!-- Vertical surface, urban type, westward facing
1140    surf_usm_v(3)%ns = num_usm_v(3)
1141!
1142!-- Allocate required attributes for horizontal surfaces - default type.
1143!-- Upward-facing (l=0) and downward-facing (l=1).
1144    DO  l = 0, 1
1145       CALL allocate_surface_attributes_h ( surf_def_h(l), nys, nyn, nxl, nxr )
1146    ENDDO
1147!
1148!-- Allocate required attributes for model top
1149    CALL allocate_surface_attributes_h_top ( surf_def_h(2), nys, nyn, nxl, nxr )
1150!
1151!-- Allocate required attributes for horizontal surfaces - natural type.
1152    DO  l = 0, 1
1153       CALL allocate_surface_attributes_h ( surf_lsm_h(l), nys, nyn, nxl, nxr )
1154    ENDDO
1155!
1156!-- Allocate required attributes for horizontal surfaces - urban type.
1157    DO  l = 0, 1
1158       CALL allocate_surface_attributes_h ( surf_usm_h(l), nys, nyn, nxl, nxr )
1159    ENDDO
1160
1161!
1162!-- Allocate required attributes for vertical surfaces.
1163!-- Northward-facing (l=0), southward-facing (l=1), eastward-facing (l=2) and westward-facing (l=3).
1164!-- Default type.
1165    DO  l = 0, 3
1166       CALL allocate_surface_attributes_v ( surf_def_v(l), nys, nyn, nxl, nxr )
1167    ENDDO
1168!
1169!-- Natural type
1170    DO  l = 0, 3
1171       CALL allocate_surface_attributes_v ( surf_lsm_v(l), nys, nyn, nxl, nxr )
1172    ENDDO
1173!
1174!-- Urban type
1175    DO  l = 0, 3
1176       CALL allocate_surface_attributes_v ( surf_usm_v(l), nys, nyn, nxl, nxr )
1177    ENDDO
1178!
1179!-- Set the flag for the existence of vertical urban/land surfaces. Therefore, sum-up the number of
1180!-- all natural and urban-type vertical surfaces and check.
1181    num_surf_v_l = 0
1182    DO  l = 0, 3
1183       num_surf_v_l = num_surf_v_l + surf_usm_v(l)%ns + surf_lsm_v(l)%ns
1184    ENDDO
1185
1186#if defined( __parallel )
1187    CALL MPI_ALLREDUCE( num_surf_v_l, num_surf_v, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
1188#else
1189    num_surf_v = num_surf_v_l
1190#endif
1191    IF ( num_surf_v > 0 )  vertical_surfaces_exist = .TRUE.
1192
1193!
1194!-- Calculate the total number of surfaces in the entire model domain of a type.
1195!-- Horizontal walls.
1196    DO  l = 0, 1
1197#if defined( __parallel )
1198       CALL MPI_ALLREDUCE( surf_def_h(l)%ns, surf_def_h(l)%ns_tot, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
1199       CALL MPI_ALLREDUCE( surf_lsm_h(l)%ns, surf_lsm_h(l)%ns_tot, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
1200       CALL MPI_ALLREDUCE( surf_usm_h(l)%ns, surf_usm_h(l)%ns_tot, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
1201#else
1202       surf_def_h(l)%ns_tot = surf_def_h(l)%ns
1203       surf_lsm_h(l)%ns_tot = surf_lsm_h(l)%ns
1204       surf_usm_h(l)%ns_tot = surf_usm_h(l)%ns
1205#endif
1206    ENDDO
1207!
1208!-- Vertical walls.
1209    DO  l = 0, 3
1210#if defined( __parallel )
1211       CALL MPI_ALLREDUCE( surf_def_v(l)%ns, surf_def_v(l)%ns_tot, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
1212       CALL MPI_ALLREDUCE( surf_lsm_v(l)%ns, surf_lsm_v(l)%ns_tot, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
1213       CALL MPI_ALLREDUCE( surf_usm_v(l)%ns, surf_usm_v(l)%ns_tot, 1, MPI_INTEGER, MPI_SUM, comm2d, ierr)
1214#else
1215       surf_def_v(l)%ns_tot = surf_def_v(l)%ns
1216       surf_lsm_v(l)%ns_tot = surf_lsm_v(l)%ns
1217       surf_usm_v(l)%ns_tot = surf_usm_v(l)%ns
1218#endif
1219    ENDDO
1220
1221 END SUBROUTINE init_surface_arrays
1222
1223
1224!--------------------------------------------------------------------------------------------------!
1225! Description:
1226! ------------
1227!> Enter horizontal and vertical surfaces.
1228!--------------------------------------------------------------------------------------------------!
1229#if defined( _OPENACC )
1230 SUBROUTINE enter_surface_arrays
1231
1232    IMPLICIT NONE
1233
1234    INTEGER(iwp) ::  l  !<
1235
1236    !$ACC ENTER DATA &
1237    !$ACC COPYIN(surf_def_h(0:2)) &
1238    !$ACC COPYIN(surf_def_v(0:3)) &
1239    !$ACC COPYIN(surf_lsm_h(0:1)) &
1240    !$ACC COPYIN(surf_lsm_v(0:3)) &
1241    !$ACC COPYIN(surf_usm_h(0:1)) &
1242    !$ACC COPYIN(surf_usm_v(0:3))
1243!
1244!-- Copy data in surf_def_h(0:2)
1245    DO  l = 0, 1
1246       CALL enter_surface_attributes_h( surf_def_h(l) )
1247    ENDDO
1248    CALL enter_surface_attributes_h_top( surf_def_h(2) )
1249!
1250!-- Copy data in surf_def_v(0:3)
1251    DO  l = 0, 3
1252       CALL enter_surface_attributes_v( surf_def_v(l) )
1253    ENDDO
1254!
1255!-- Copy data in surf_lsm_h
1256    DO  l = 0, 1
1257       CALL enter_surface_attributes_h( surf_lsm_h(l) )
1258    ENDDO
1259!
1260!-- Copy data in surf_lsm_v(0:3)
1261    DO  l = 0, 3
1262       CALL enter_surface_attributes_v( surf_lsm_v(l) )
1263    ENDDO
1264!
1265!-- Copy data in surf_usm_h
1266    DO  l = 0, 1
1267       CALL enter_surface_attributes_h( surf_usm_h(l) )
1268    ENDDO
1269!
1270!-- Copy data in surf_usm_v(0:3)
1271    DO  l = 0, 3
1272       CALL enter_surface_attributes_v( surf_usm_v(l) )
1273    ENDDO
1274
1275 END SUBROUTINE enter_surface_arrays
1276#endif
1277
1278!--------------------------------------------------------------------------------------------------!
1279! Description:
1280! ------------
1281!> Exit horizontal and vertical surfaces.
1282!--------------------------------------------------------------------------------------------------!
1283#if defined( _OPENACC )
1284 SUBROUTINE exit_surface_arrays
1285
1286    IMPLICIT NONE
1287
1288    INTEGER(iwp) ::  l  !<
1289!
1290!-- Delete data in surf_def_h(0:2)
1291    DO  l = 0, 1
1292       CALL exit_surface_attributes_h( surf_def_h(l) )
1293    ENDDO
1294    CALL exit_surface_attributes_h( surf_def_h(2) )
1295!
1296!-- Delete data in surf_def_v(0:3)
1297    DO  l = 0, 3
1298       CALL exit_surface_attributes_v( surf_def_v(l) )
1299    ENDDO
1300!
1301!-- Delete data in surf_lsm_h
1302    DO  l = 0, 1
1303       CALL exit_surface_attributes_h( surf_lsm_h(l) )
1304    ENDDO
1305!
1306!-- Delete data in surf_lsm_v(0:3)
1307    DO  l = 0, 3
1308       CALL exit_surface_attributes_v( surf_lsm_v(l) )
1309    ENDDO
1310!
1311!-- Delete data in surf_usm_h
1312    DO  l = 0, 1
1313       CALL exit_surface_attributes_h( surf_usm_h(l) )
1314    ENDDO
1315!
1316!-- Delete data in surf_usm_v(0:3)
1317    DO  l = 0, 3
1318       CALL exit_surface_attributes_v( surf_usm_v(l) )
1319    ENDDO
1320
1321    !$ACC EXIT DATA &
1322    !$ACC DELETE(surf_def_h(0:2)) &
1323    !$ACC DELETE(surf_def_v(0:3)) &
1324    !$ACC DELETE(surf_lsm_h(0:1)) &
1325    !$ACC DELETE(surf_lsm_v(0:3)) &
1326    !$ACC DELETE(surf_usm_h(0:1)) &
1327    !$ACC DELETE(surf_usm_v(0:3))
1328
1329 END SUBROUTINE exit_surface_arrays
1330#endif
1331
1332!--------------------------------------------------------------------------------------------------!
1333! Description:
1334! ------------
1335!> Deallocating memory for upward and downward-facing horizontal surface types, except for top
1336!> fluxes.
1337!--------------------------------------------------------------------------------------------------!
1338 SUBROUTINE deallocate_surface_attributes_h( surfaces )
1339
1340    IMPLICIT NONE
1341
1342
1343    TYPE(surf_type) ::  surfaces  !< respective surface type
1344
1345
1346    DEALLOCATE ( surfaces%start_index )
1347    DEALLOCATE ( surfaces%end_index )
1348!
1349!-- Indices to locate surface element
1350    DEALLOCATE ( surfaces%i )
1351    DEALLOCATE ( surfaces%j )
1352    DEALLOCATE ( surfaces%k )
1353!
1354!-- Surface-layer height
1355    DEALLOCATE ( surfaces%z_mo )
1356!
1357!-- Surface orientation
1358    DEALLOCATE ( surfaces%facing )
1359!
1360!-- Surface-parallel wind velocity
1361    DEALLOCATE ( surfaces%uvw_abs )
1362!
1363!-- Pre-calculated ln(z/z0)
1364    DEALLOCATE ( surfaces%ln_z_z0  )
1365    DEALLOCATE ( surfaces%ln_z_z0h )
1366    DEALLOCATE ( surfaces%ln_z_z0q )
1367!
1368!-- Roughness
1369    DEALLOCATE ( surfaces%z0 )
1370    DEALLOCATE ( surfaces%z0h )
1371    DEALLOCATE ( surfaces%z0q )
1372!
1373!-- Friction velocity
1374    DEALLOCATE ( surfaces%us )
1375!
1376!-- Stability parameter
1377    DEALLOCATE ( surfaces%ol )
1378!
1379!-- Bulk Richardson number
1380    DEALLOCATE ( surfaces%rib )
1381!
1382!-- Vertical momentum fluxes of u and v
1383    DEALLOCATE ( surfaces%usws )
1384    DEALLOCATE ( surfaces%vsws )
1385!
1386!-- Required in production_e
1387    IF ( .NOT. constant_diffusion )  THEN
1388       DEALLOCATE ( surfaces%u_0 )
1389       DEALLOCATE ( surfaces%v_0 )
1390    ENDIF
1391!
1392!-- Characteristic temperature and surface flux of sensible heat
1393    DEALLOCATE ( surfaces%ts )
1394    DEALLOCATE ( surfaces%shf )
1395!
1396!-- Surface temperature
1397    DEALLOCATE ( surfaces%pt_surface )
1398!
1399!-- Characteristic humidity and surface flux of latent heat
1400    IF ( humidity )  THEN
1401       DEALLOCATE ( surfaces%qs )
1402       DEALLOCATE ( surfaces%qsws )
1403       DEALLOCATE ( surfaces%q_surface   )
1404       DEALLOCATE ( surfaces%vpt_surface )
1405    ENDIF
1406!
1407!-- Characteristic scalar and surface flux of scalar
1408    IF ( passive_scalar )  THEN
1409       DEALLOCATE ( surfaces%ss )
1410       DEALLOCATE ( surfaces%ssws )
1411    ENDIF
1412!
1413!-- Scaling parameter (cs*) and surface flux of chemical species
1414    IF ( air_chemistry )  THEN
1415       DEALLOCATE ( surfaces%css )
1416       DEALLOCATE ( surfaces%cssws )
1417    ENDIF
1418!
1419!-- Arrays for storing potential temperature and mixing ratio at first grid level
1420    DEALLOCATE ( surfaces%pt1 )
1421    DEALLOCATE ( surfaces%qv1 )
1422    DEALLOCATE ( surfaces%vpt1 )
1423
1424!
1425!--
1426    IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison)  THEN
1427       DEALLOCATE ( surfaces%qcs )
1428       DEALLOCATE ( surfaces%ncs )
1429       DEALLOCATE ( surfaces%qcsws )
1430       DEALLOCATE ( surfaces%ncsws )
1431    ENDIF
1432!
1433!--
1434    IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert)  THEN
1435       DEALLOCATE ( surfaces%qrs )
1436       DEALLOCATE ( surfaces%nrs )
1437       DEALLOCATE ( surfaces%qrsws )
1438       DEALLOCATE ( surfaces%nrsws )
1439    ENDIF
1440!
1441!--
1442    IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase)  THEN
1443       DEALLOCATE ( surfaces%qis )
1444       DEALLOCATE ( surfaces%nis )
1445       DEALLOCATE ( surfaces%qisws )
1446       DEALLOCATE ( surfaces%nisws )
1447    ENDIF
1448!
1449!-- Salinity surface flux
1450    IF ( ocean_mode )  DEALLOCATE ( surfaces%sasws )
1451
1452 END SUBROUTINE deallocate_surface_attributes_h
1453
1454
1455!--------------------------------------------------------------------------------------------------!
1456! Description:
1457! ------------
1458!> Allocating memory for upward and downward-facing horizontal surface types, except for top fluxes.
1459!--------------------------------------------------------------------------------------------------!
1460 SUBROUTINE allocate_surface_attributes_h( surfaces, nys_l, nyn_l, nxl_l, nxr_l )
1461
1462    IMPLICIT NONE
1463
1464    INTEGER(iwp) ::  nyn_l  !< north bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1465    INTEGER(iwp) ::  nys_l  !< south bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1466    INTEGER(iwp) ::  nxl_l  !< west bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1467    INTEGER(iwp) ::  nxr_l  !< east bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1468
1469    TYPE(surf_type) ::  surfaces  !< respective surface type
1470
1471!
1472!-- Allocate arrays for start and end index of horizontal surface type for each (j,i)-grid point.
1473!-- This is required e.g. in diffion_x, which is called for each (j,i). In order to find the
1474!-- location where the respective flux is store within the surface-type, start- and end-index are
1475!-- stored for each (j,i). For example, each (j,i) can have several entries where fluxes for
1476!-- horizontal surfaces might be stored, e.g. for overhanging structures where several upward-facing
1477!-- surfaces might exist for given (j,i). If no surface of respective type exist at current (j,i),
1478!-- set indicies such that loop in diffusion routines will not be entered.
1479    ALLOCATE ( surfaces%start_index(nys_l:nyn_l,nxl_l:nxr_l) )
1480    ALLOCATE ( surfaces%end_index(nys_l:nyn_l,nxl_l:nxr_l) )
1481    surfaces%start_index = 0
1482    surfaces%end_index   = -1
1483!
1484!-- Indices to locate surface element
1485    ALLOCATE ( surfaces%i(1:surfaces%ns) )
1486    ALLOCATE ( surfaces%j(1:surfaces%ns) )
1487    ALLOCATE ( surfaces%k(1:surfaces%ns) )
1488!
1489!-- Surface-layer height
1490    ALLOCATE ( surfaces%z_mo(1:surfaces%ns) )
1491!
1492!-- Surface orientation
1493    ALLOCATE ( surfaces%facing(1:surfaces%ns) )
1494!
1495!-- Surface-parallel wind velocity
1496    ALLOCATE ( surfaces%uvw_abs(1:surfaces%ns) )
1497!
1498!-- Precalculated ln(z/z0)
1499    ALLOCATE( surfaces%ln_z_z0(1:surfaces%ns)  )
1500    ALLOCATE( surfaces%ln_z_z0h(1:surfaces%ns) )
1501    ALLOCATE( surfaces%ln_z_z0q(1:surfaces%ns) )
1502!
1503!-- Roughness
1504    ALLOCATE ( surfaces%z0(1:surfaces%ns)  )
1505    ALLOCATE ( surfaces%z0h(1:surfaces%ns) )
1506    ALLOCATE ( surfaces%z0q(1:surfaces%ns) )
1507!
1508!-- Friction velocity
1509    ALLOCATE ( surfaces%us(1:surfaces%ns) )
1510!
1511!-- Stability parameter
1512    ALLOCATE ( surfaces%ol(1:surfaces%ns) )
1513!
1514!-- Bulk Richardson number
1515    ALLOCATE ( surfaces%rib(1:surfaces%ns) )
1516!
1517!-- Vertical momentum fluxes of u and v
1518    ALLOCATE ( surfaces%usws(1:surfaces%ns) )
1519    ALLOCATE ( surfaces%vsws(1:surfaces%ns) )
1520!
1521!-- Required in production_e
1522    IF ( .NOT. constant_diffusion )  THEN
1523       ALLOCATE ( surfaces%u_0(1:surfaces%ns) )
1524       ALLOCATE ( surfaces%v_0(1:surfaces%ns) )
1525    ENDIF
1526!
1527!-- Characteristic temperature and surface flux of sensible heat
1528    ALLOCATE ( surfaces%ts(1:surfaces%ns) )
1529    ALLOCATE ( surfaces%shf(1:surfaces%ns) )
1530!
1531!-- Surface temperature
1532    ALLOCATE ( surfaces%pt_surface(1:surfaces%ns) )
1533!
1534!-- Characteristic humidity, surface flux of latent heat, and surface virtual potential temperature
1535    IF ( humidity )  THEN
1536       ALLOCATE ( surfaces%qs(1:surfaces%ns) )
1537       ALLOCATE ( surfaces%qsws(1:surfaces%ns) )
1538       ALLOCATE ( surfaces%q_surface(1:surfaces%ns) )
1539       ALLOCATE ( surfaces%vpt_surface(1:surfaces%ns) )
1540    ENDIF
1541
1542!
1543!-- Characteristic scalar and surface flux of scalar
1544    IF ( passive_scalar )  THEN
1545       ALLOCATE ( surfaces%ss(1:surfaces%ns) )
1546       ALLOCATE ( surfaces%ssws(1:surfaces%ns) )
1547    ENDIF
1548!
1549!-- Scaling parameter (cs*) and surface flux of chemical species
1550    IF ( air_chemistry )  THEN
1551       ALLOCATE ( surfaces%css(1:nvar,1:surfaces%ns) )
1552       ALLOCATE ( surfaces%cssws(1:nvar,1:surfaces%ns) )
1553    ENDIF
1554!
1555!-- Arrays for storing potential temperature and mixing ratio at first grid level
1556    ALLOCATE ( surfaces%pt1(1:surfaces%ns) )
1557    ALLOCATE ( surfaces%qv1(1:surfaces%ns) )
1558    ALLOCATE ( surfaces%vpt1(1:surfaces%ns) )
1559!
1560!--
1561    IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison)  THEN
1562       ALLOCATE ( surfaces%qcs(1:surfaces%ns) )
1563       ALLOCATE ( surfaces%ncs(1:surfaces%ns) )
1564       ALLOCATE ( surfaces%qcsws(1:surfaces%ns) )
1565       ALLOCATE ( surfaces%ncsws(1:surfaces%ns) )
1566    ENDIF
1567!
1568!--
1569    IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert)  THEN
1570       ALLOCATE ( surfaces%qrs(1:surfaces%ns) )
1571       ALLOCATE ( surfaces%nrs(1:surfaces%ns) )
1572       ALLOCATE ( surfaces%qrsws(1:surfaces%ns) )
1573       ALLOCATE ( surfaces%nrsws(1:surfaces%ns) )
1574    ENDIF
1575
1576!
1577!--
1578    IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase)  THEN
1579       ALLOCATE ( surfaces%qis(1:surfaces%ns) )
1580       ALLOCATE ( surfaces%nis(1:surfaces%ns) )
1581       ALLOCATE ( surfaces%qisws(1:surfaces%ns) )
1582       ALLOCATE ( surfaces%nisws(1:surfaces%ns) )
1583    ENDIF
1584
1585!
1586!-- Salinity surface flux
1587    IF ( ocean_mode )  ALLOCATE ( surfaces%sasws(1:surfaces%ns) )
1588
1589 END SUBROUTINE allocate_surface_attributes_h
1590
1591
1592!--------------------------------------------------------------------------------------------------!
1593! Description:
1594! ------------
1595!> Exit memory for upward and downward-facing horizontal surface types, except for top fluxes.
1596!--------------------------------------------------------------------------------------------------!
1597#if defined( _OPENACC )
1598 SUBROUTINE exit_surface_attributes_h( surfaces )
1599
1600    IMPLICIT NONE
1601
1602    TYPE(surf_type) ::  surfaces  !< respective surface type
1603
1604    !$ACC EXIT DATA &
1605    !$ACC DELETE(surfaces%start_index(nys:nyn,nxl:nxr)) &
1606    !$ACC DELETE(surfaces%end_index(nys:nyn,nxl:nxr)) &
1607    !$ACC DELETE(surfaces%i(1:surfaces%ns)) &
1608    !$ACC DELETE(surfaces%j(1:surfaces%ns)) &
1609    !$ACC DELETE(surfaces%k(1:surfaces%ns)) &
1610    !$ACC DELETE(surfaces%z_mo(1:surfaces%ns)) &
1611    !$ACC DELETE(surfaces%uvw_abs(1:surfaces%ns)) &
1612    !$ACC DELETE(surfaces%ln_z_z0(1:surfaces%ns)) &
1613    !$ACC DELETE(surfaces%ln_z_z0h(1:surfaces%ns)) &
1614    !$ACC DELETE(surfaces%ln_z_z0q(1:surfaces%ns)) &
1615    !$ACC DELETE(surfaces%z0(1:surfaces%ns)) &
1616    !$ACC DELETE(surfaces%z0h(1:surfaces%ns)) &
1617    !$ACC DELETE(surfaces%z0q(1:surfaces%ns)) &
1618    !$ACC COPYOUT(surfaces%us(1:surfaces%ns)) &
1619    !$ACC COPYOUT(surfaces%ol(1:surfaces%ns)) &
1620    !$ACC DELETE(surfaces%rib(1:surfaces%ns)) &
1621    !$ACC COPYOUT(surfaces%usws(1:surfaces%ns)) &
1622    !$ACC COPYOUT(surfaces%vsws(1:surfaces%ns)) &
1623    !$ACC COPYOUT(surfaces%ts(1:surfaces%ns)) &
1624    !$ACC COPYOUT(surfaces%shf(1:surfaces%ns)) &
1625    !$ACC DELETE(surfaces%pt_surface(1:surfaces%ns)) &
1626    !$ACC DELETE(surfaces%pt1(1:surfaces%ns)) &
1627    !$ACC DELETE(surfaces%qv1(1:surfaces%ns))
1628
1629    IF ( .NOT. constant_diffusion )  THEN
1630       !$ACC EXIT DATA &
1631       !$ACC DELETE(surfaces%u_0(1:surfaces%ns)) &
1632       !$ACC DELETE(surfaces%v_0(1:surfaces%ns))
1633    ENDIF
1634
1635 END SUBROUTINE exit_surface_attributes_h
1636#endif
1637
1638!--------------------------------------------------------------------------------------------------!
1639! Description:
1640! ------------
1641!> Enter memory for upward and downward-facing horizontal surface types, except for top fluxes.
1642!--------------------------------------------------------------------------------------------------!
1643#if defined( _OPENACC )
1644 SUBROUTINE enter_surface_attributes_h( surfaces )
1645
1646    IMPLICIT NONE
1647
1648    TYPE(surf_type) ::  surfaces  !< respective surface type
1649
1650    !$ACC ENTER DATA &
1651    !$ACC COPYIN(surfaces%start_index(nys:nyn,nxl:nxr)) &
1652    !$ACC COPYIN(surfaces%end_index(nys:nyn,nxl:nxr)) &
1653    !$ACC COPYIN(surfaces%i(1:surfaces%ns)) &
1654    !$ACC COPYIN(surfaces%j(1:surfaces%ns)) &
1655    !$ACC COPYIN(surfaces%k(1:surfaces%ns)) &
1656    !$ACC COPYIN(surfaces%z_mo(1:surfaces%ns)) &
1657    !$ACC COPYIN(surfaces%uvw_abs(1:surfaces%ns)) &
1658    !$ACC COPYIN(surfaces%ln_z_z0(1:surfaces%ns)) &
1659    !$ACC COPYIN(surfaces%ln_z_z0h(1:surfaces%ns)) &
1660    !$ACC COPYIN(surfaces%ln_z_z0q(1:surfaces%ns)) &
1661    !$ACC COPYIN(surfaces%z0(1:surfaces%ns)) &
1662    !$ACC COPYIN(surfaces%z0h(1:surfaces%ns)) &
1663    !$ACC COPYIN(surfaces%z0q(1:surfaces%ns)) &
1664    !$ACC COPYIN(surfaces%us(1:surfaces%ns)) &
1665    !$ACC COPYIN(surfaces%ol(1:surfaces%ns)) &
1666    !$ACC COPYIN(surfaces%rib(1:surfaces%ns)) &
1667    !$ACC COPYIN(surfaces%usws(1:surfaces%ns)) &
1668    !$ACC COPYIN(surfaces%vsws(1:surfaces%ns)) &
1669    !$ACC COPYIN(surfaces%ts(1:surfaces%ns)) &
1670    !$ACC COPYIN(surfaces%shf(1:surfaces%ns)) &
1671    !$ACC COPYIN(surfaces%pt1(1:surfaces%ns)) &
1672    !$ACC COPYIN(surfaces%qv1(1:surfaces%ns)) &
1673    !$ACC COPYIN(surfaces%pt_surface(1:surfaces%ns))
1674
1675    IF ( .NOT. constant_diffusion )  THEN
1676       !$ACC ENTER DATA &
1677       !$ACC COPYIN(surfaces%u_0(1:surfaces%ns)) &
1678       !$ACC COPYIN(surfaces%v_0(1:surfaces%ns))
1679    ENDIF
1680
1681 END SUBROUTINE enter_surface_attributes_h
1682#endif
1683
1684!--------------------------------------------------------------------------------------------------!
1685! Description:
1686! ------------
1687!> Deallocating memory for model-top fluxes
1688!--------------------------------------------------------------------------------------------------!
1689 SUBROUTINE deallocate_surface_attributes_h_top( surfaces )
1690
1691    IMPLICIT NONE
1692
1693
1694    TYPE(surf_type) ::  surfaces !< respective surface type
1695
1696    DEALLOCATE ( surfaces%start_index )
1697    DEALLOCATE ( surfaces%end_index )
1698!
1699!-- Indices to locate surface (model-top) element
1700    DEALLOCATE ( surfaces%i )
1701    DEALLOCATE ( surfaces%j )
1702    DEALLOCATE ( surfaces%k )
1703
1704    IF ( .NOT. constant_diffusion )  THEN
1705       DEALLOCATE ( surfaces%u_0 )
1706       DEALLOCATE ( surfaces%v_0 )
1707    ENDIF
1708!
1709!-- Vertical momentum fluxes of u and v
1710    DEALLOCATE ( surfaces%usws )
1711    DEALLOCATE ( surfaces%vsws )
1712!
1713!-- Sensible heat flux
1714    DEALLOCATE ( surfaces%shf )
1715!
1716!-- Latent heat flux
1717    IF ( humidity .OR. coupling_mode == 'ocean_to_atmosphere')  THEN
1718       DEALLOCATE ( surfaces%qsws )
1719    ENDIF
1720!
1721!-- Scalar flux
1722    IF ( passive_scalar )  THEN
1723       DEALLOCATE ( surfaces%ssws )
1724    ENDIF
1725!
1726!-- Chemical species flux
1727    IF ( air_chemistry )  THEN
1728       DEALLOCATE ( surfaces%cssws )
1729    ENDIF
1730!
1731!--
1732    IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison)  THEN
1733       DEALLOCATE ( surfaces%qcsws )
1734       DEALLOCATE ( surfaces%ncsws )
1735    ENDIF
1736!
1737!--
1738    IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert)  THEN
1739       DEALLOCATE ( surfaces%qrsws )
1740       DEALLOCATE ( surfaces%nrsws )
1741    ENDIF
1742
1743!
1744!--
1745    IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase)  THEN
1746       DEALLOCATE ( surfaces%qisws )
1747       DEALLOCATE ( surfaces%nisws )
1748    ENDIF
1749!
1750!-- Salinity flux
1751    IF ( ocean_mode )  DEALLOCATE ( surfaces%sasws )
1752
1753 END SUBROUTINE deallocate_surface_attributes_h_top
1754
1755
1756!--------------------------------------------------------------------------------------------------!
1757! Description:
1758! ------------
1759!> Allocating memory for model-top fluxes
1760!--------------------------------------------------------------------------------------------------!
1761 SUBROUTINE allocate_surface_attributes_h_top( surfaces, nys_l, nyn_l, nxl_l, nxr_l )
1762
1763    IMPLICIT NONE
1764
1765    INTEGER(iwp) ::  nyn_l  !< north bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1766    INTEGER(iwp) ::  nys_l  !< south bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1767    INTEGER(iwp) ::  nxl_l  !< west bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1768    INTEGER(iwp) ::  nxr_l  !< east bound of local 2d array start/end_index, is equal to nyn, except for restart-array
1769
1770    TYPE(surf_type) ::  surfaces !< respective surface type
1771
1772    ALLOCATE ( surfaces%start_index(nys_l:nyn_l,nxl_l:nxr_l) )
1773    ALLOCATE ( surfaces%end_index(nys_l:nyn_l,nxl_l:nxr_l) )
1774    surfaces%start_index = 0
1775    surfaces%end_index   = -1
1776!
1777!-- Indices to locate surface (model-top) element
1778    ALLOCATE ( surfaces%i(1:surfaces%ns) )
1779    ALLOCATE ( surfaces%j(1:surfaces%ns) )
1780    ALLOCATE ( surfaces%k(1:surfaces%ns) )
1781
1782    IF ( .NOT. constant_diffusion )  THEN
1783       ALLOCATE ( surfaces%u_0(1:surfaces%ns) )
1784       ALLOCATE ( surfaces%v_0(1:surfaces%ns) )
1785    ENDIF
1786!
1787!-- Vertical momentum fluxes of u and v
1788    ALLOCATE ( surfaces%usws(1:surfaces%ns) )
1789    ALLOCATE ( surfaces%vsws(1:surfaces%ns) )
1790!
1791!-- Sensible heat flux
1792    ALLOCATE ( surfaces%shf(1:surfaces%ns) )
1793!
1794!-- Latent heat flux
1795    IF ( humidity .OR. coupling_mode == 'ocean_to_atmosphere')  THEN
1796       ALLOCATE ( surfaces%qsws(1:surfaces%ns) )
1797    ENDIF
1798!
1799!-- Scalar flux
1800    IF ( passive_scalar )  THEN
1801       ALLOCATE ( surfaces%ssws(1:surfaces%ns) )
1802    ENDIF
1803!
1804!-- Chemical species flux
1805    IF ( air_chemistry )  THEN
1806       ALLOCATE ( surfaces%cssws(1:nvar,1:surfaces%ns) )
1807    ENDIF
1808!
1809!--
1810    IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison )  THEN
1811       ALLOCATE ( surfaces%qcsws(1:surfaces%ns) )
1812       ALLOCATE ( surfaces%ncsws(1:surfaces%ns) )
1813    ENDIF
1814!
1815!--
1816    IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert )  THEN
1817       ALLOCATE ( surfaces%qrsws(1:surfaces%ns) )
1818       ALLOCATE ( surfaces%nrsws(1:surfaces%ns) )
1819    ENDIF
1820
1821!
1822!--
1823    IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase )  THEN
1824       ALLOCATE ( surfaces%qisws(1:surfaces%ns) )
1825       ALLOCATE ( surfaces%nisws(1:surfaces%ns) )
1826    ENDIF
1827!
1828!-- Salinity flux
1829    IF ( ocean_mode )  ALLOCATE ( surfaces%sasws(1:surfaces%ns) )
1830
1831 END SUBROUTINE allocate_surface_attributes_h_top
1832
1833
1834!--------------------------------------------------------------------------------------------------!
1835! Description:
1836! ------------
1837!> Exit memory for model-top fluxes.
1838!--------------------------------------------------------------------------------------------------!
1839#if defined( _OPENACC )
1840 SUBROUTINE exit_surface_attributes_h_top( surfaces )
1841
1842    IMPLICIT NONE
1843
1844    TYPE(surf_type) ::  surfaces  !< respective surface type
1845
1846    !$ACC EXIT DATA &
1847    !$ACC DELETE(surfaces%start_index(nys:nyn,nxl:nxr)) &
1848    !$ACC DELETE(surfaces%end_index(nys:nyn,nxl:nxr)) &
1849    !$ACC DELETE(surfaces%i(1:surfaces%ns)) &
1850    !$ACC DELETE(surfaces%j(1:surfaces%ns)) &
1851    !$ACC DELETE(surfaces%k(1:surfaces%ns)) &
1852    !$ACC DELETE(surfaces%usws(1:surfaces%ns)) &
1853    !$ACC DELETE(surfaces%vsws(1:surfaces%ns)) &
1854    !$ACC DELETE(surfaces%shf(1:surfaces%ns))
1855
1856    IF ( .NOT. constant_diffusion )  THEN
1857       !$ACC EXIT DATA &
1858       !$ACC DELETE(surfaces%u_0(1:surfaces%ns)) &
1859       !$ACC DELETE(surfaces%v_0(1:surfaces%ns))
1860    ENDIF
1861
1862 END SUBROUTINE exit_surface_attributes_h_top
1863#endif
1864
1865!--------------------------------------------------------------------------------------------------!
1866! Description:
1867! ------------
1868!> Enter memory for model-top fluxes.
1869!--------------------------------------------------------------------------------------------------!
1870#if defined( _OPENACC )
1871 SUBROUTINE enter_surface_attributes_h_top( surfaces )
1872
1873    IMPLICIT NONE
1874
1875    TYPE(surf_type) ::  surfaces  !< respective surface type
1876
1877    !$ACC ENTER DATA &
1878    !$ACC COPYIN(surfaces%start_index(nys:nyn,nxl:nxr)) &
1879    !$ACC COPYIN(surfaces%end_index(nys:nyn,nxl:nxr)) &
1880    !$ACC COPYIN(surfaces%i(1:surfaces%ns)) &
1881    !$ACC COPYIN(surfaces%j(1:surfaces%ns)) &
1882    !$ACC COPYIN(surfaces%k(1:surfaces%ns)) &
1883    !$ACC COPYIN(surfaces%usws(1:surfaces%ns)) &
1884    !$ACC COPYIN(surfaces%vsws(1:surfaces%ns)) &
1885    !$ACC COPYIN(surfaces%shf(1:surfaces%ns))
1886
1887    IF ( .NOT. constant_diffusion )  THEN
1888       !$ACC ENTER DATA &
1889       !$ACC COPYIN(surfaces%u_0(1:surfaces%ns)) &
1890       !$ACC COPYIN(surfaces%v_0(1:surfaces%ns))
1891    ENDIF
1892
1893 END SUBROUTINE enter_surface_attributes_h_top
1894#endif
1895
1896!--------------------------------------------------------------------------------------------------!
1897! Description:
1898! ------------
1899!> Deallocating memory for vertical surface types.
1900!--------------------------------------------------------------------------------------------------!
1901 SUBROUTINE deallocate_surface_attributes_v( surfaces )
1902
1903    IMPLICIT NONE
1904
1905
1906    TYPE(surf_type) ::  surfaces !< respective surface type
1907
1908!
1909!-- Allocate arrays for start and end index of vertical surface type for each (j,i)-grid point. This
1910!-- is required in diffion_x, which is called for each (j,i). In order to find the location where
1911!-- the respective flux is store within the surface-type, start- and end-index are stored for each
1912!-- (j,i). For example, each (j,i) can have several entries where fluxes for vertical surfaces might
1913!-- be stored. In the flat case, where no vertical walls exit, set indicies such that loop in
1914!-- diffusion routines will not be entered.
1915    DEALLOCATE ( surfaces%start_index )
1916    DEALLOCATE ( surfaces%end_index )
1917!
1918!-- Indices to locate surface element.
1919    DEALLOCATE ( surfaces%i )
1920    DEALLOCATE ( surfaces%j )
1921    DEALLOCATE ( surfaces%k )
1922!
1923!-- Surface-layer height
1924    DEALLOCATE ( surfaces%z_mo )
1925!
1926!-- Surface orientation
1927    DEALLOCATE ( surfaces%facing )
1928!
1929!-- Surface parallel wind velocity
1930    DEALLOCATE ( surfaces%uvw_abs )
1931!
1932!-- Precalculated ln(z/z0)
1933    DEALLOCATE ( surfaces%ln_z_z0  )
1934    DEALLOCATE ( surfaces%ln_z_z0h )
1935    DEALLOCATE ( surfaces%ln_z_z0q )
1936!
1937!-- Roughness
1938    DEALLOCATE ( surfaces%z0 )
1939    DEALLOCATE ( surfaces%z0h )
1940    DEALLOCATE ( surfaces%z0q )
1941!
1942!-- Friction velocity
1943    DEALLOCATE ( surfaces%us )
1944!
1945!-- Allocate Obukhov length and bulk Richardson number. Actually, at vertical surfaces these are
1946!-- only required for natural surfaces.
1947!-- For natural land surfaces
1948    DEALLOCATE( surfaces%ol )
1949    DEALLOCATE( surfaces%rib )
1950!
1951!-- Allocate arrays for surface momentum fluxes for u and v. For u at north- and south-facing
1952!-- surfaces, for v at east- and west-facing surfaces.
1953    DEALLOCATE ( surfaces%mom_flux_uv )
1954!
1955!-- Allocate array for surface momentum flux for w - wsus and wsvs
1956    DEALLOCATE ( surfaces%mom_flux_w )
1957!
1958!-- Allocate array for surface momentum flux for subgrid-scale tke wsus and wsvs; first index usvs
1959!-- or vsws, second index for wsus or wsvs, depending on surface.
1960    DEALLOCATE ( surfaces%mom_flux_tke )
1961!
1962!-- Characteristic temperature and surface flux of sensible heat
1963    DEALLOCATE ( surfaces%ts )
1964    DEALLOCATE ( surfaces%shf )
1965!
1966!-- Surface temperature
1967    DEALLOCATE ( surfaces%pt_surface )
1968!
1969!-- Characteristic humidity and surface flux of latent heat
1970    IF ( humidity )  THEN
1971       DEALLOCATE ( surfaces%qs )
1972       DEALLOCATE ( surfaces%qsws )
1973       DEALLOCATE ( surfaces%q_surface )
1974       DEALLOCATE ( surfaces%vpt_surface )
1975    ENDIF
1976!
1977!-- Characteristic scalar and surface flux of scalar
1978    IF ( passive_scalar )  THEN
1979       DEALLOCATE ( surfaces%ss )
1980       DEALLOCATE ( surfaces%ssws )
1981    ENDIF
1982!
1983!-- Scaling parameter (cs*) and surface flux of chemical species
1984    IF ( air_chemistry )  THEN
1985       DEALLOCATE ( surfaces%css )
1986       DEALLOCATE ( surfaces%cssws )
1987    ENDIF
1988!
1989!-- Arrays for storing potential temperature and mixing ratio at first grid level
1990    DEALLOCATE ( surfaces%pt1 )
1991    DEALLOCATE ( surfaces%qv1 )
1992    DEALLOCATE ( surfaces%vpt1 )
1993
1994    IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison)  THEN
1995       DEALLOCATE ( surfaces%qcs )
1996       DEALLOCATE ( surfaces%ncs )
1997       DEALLOCATE ( surfaces%qcsws )
1998       DEALLOCATE ( surfaces%ncsws )
1999    ENDIF
2000
2001    IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert)  THEN
2002       DEALLOCATE ( surfaces%qrs )
2003       DEALLOCATE ( surfaces%nrs )
2004       DEALLOCATE ( surfaces%qrsws )
2005       DEALLOCATE ( surfaces%nrsws )
2006    ENDIF
2007
2008    IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase)  THEN
2009       DEALLOCATE ( surfaces%qis )
2010       DEALLOCATE ( surfaces%nis )
2011       DEALLOCATE ( surfaces%qisws )
2012       DEALLOCATE ( surfaces%nisws )
2013    ENDIF
2014
2015!
2016!-- Salinity surface flux
2017    IF ( ocean_mode )  DEALLOCATE ( surfaces%sasws )
2018
2019 END SUBROUTINE deallocate_surface_attributes_v
2020
2021
2022!--------------------------------------------------------------------------------------------------!
2023! Description:
2024! ------------
2025!> Allocating memory for vertical surface types.
2026!--------------------------------------------------------------------------------------------------!
2027 SUBROUTINE allocate_surface_attributes_v( surfaces, nys_l, nyn_l, nxl_l, nxr_l )
2028
2029    IMPLICIT NONE
2030
2031    INTEGER(iwp) ::  nyn_l  !< north bound of local 2d array start/end_index, is equal to nyn, except for restart-array
2032    INTEGER(iwp) ::  nys_l  !< south bound of local 2d array start/end_index, is equal to nyn, except for restart-array
2033    INTEGER(iwp) ::  nxl_l  !< west bound of local 2d array start/end_index, is equal to nyn, except for restart-array
2034    INTEGER(iwp) ::  nxr_l  !< east bound of local 2d array start/end_index, is equal to nyn, except for restart-array
2035
2036    TYPE(surf_type) ::  surfaces !< respective surface type
2037
2038!
2039!-- Allocate arrays for start and end index of vertical surface type for each (j,i)-grid point. This
2040!-- is required in diffion_x, which is called for each (j,i). In order to find the location where
2041!-- the respective flux is store within the surface-type, start- and end-index are stored for each
2042!-- (j,i). For example, each (j,i) can have several entries where fluxes for vertical surfaces might
2043!-- be stored. In the flat case, where no vertical walls exit, set indicies such that loop in
2044!-- diffusion routines will not be entered.
2045    ALLOCATE ( surfaces%start_index(nys_l:nyn_l,nxl_l:nxr_l) )
2046    ALLOCATE ( surfaces%end_index(nys_l:nyn_l,nxl_l:nxr_l) )
2047    surfaces%start_index = 0
2048    surfaces%end_index   = -1
2049!
2050!-- Indices to locate surface element.
2051    ALLOCATE ( surfaces%i(1:surfaces%ns) )
2052    ALLOCATE ( surfaces%j(1:surfaces%ns) )
2053    ALLOCATE ( surfaces%k(1:surfaces%ns) )
2054!
2055!-- Surface-layer height
2056    ALLOCATE ( surfaces%z_mo(1:surfaces%ns) )
2057!
2058!-- Surface orientation
2059    ALLOCATE ( surfaces%facing(1:surfaces%ns) )
2060!
2061!-- Surface parallel wind velocity
2062    ALLOCATE ( surfaces%uvw_abs(1:surfaces%ns) )
2063!
2064!-- Precalculated ln(z/z0)
2065    ALLOCATE( surfaces%ln_z_z0(1:surfaces%ns) )
2066    ALLOCATE( surfaces%ln_z_z0h(1:surfaces%ns) )
2067    ALLOCATE( surfaces%ln_z_z0q(1:surfaces%ns) )
2068!
2069!-- Roughness
2070    ALLOCATE ( surfaces%z0(1:surfaces%ns)  )
2071    ALLOCATE ( surfaces%z0h(1:surfaces%ns) )
2072    ALLOCATE ( surfaces%z0q(1:surfaces%ns) )
2073
2074!
2075!-- Friction velocity
2076    ALLOCATE ( surfaces%us(1:surfaces%ns) )
2077!
2078!-- Allocate Obukhov length and bulk Richardson number. Actually, at vertical surfaces these are
2079!-- only required for natural surfaces.
2080!-- For natural land surfaces
2081    ALLOCATE( surfaces%ol(1:surfaces%ns) )
2082    ALLOCATE( surfaces%rib(1:surfaces%ns) )
2083!
2084!-- Allocate arrays for surface momentum fluxes for u and v. For u at north- and south-facing
2085!-- surfaces, for v at east- and west-facing surfaces.
2086    ALLOCATE ( surfaces%mom_flux_uv(1:surfaces%ns) )
2087!
2088!-- Allocate array for surface momentum flux for w - wsus and wsvs
2089    ALLOCATE ( surfaces%mom_flux_w(1:surfaces%ns) )
2090!
2091!-- Allocate array for surface momentum flux for subgrid-scale tke wsus and wsvs; first index usvs
2092!-- or vsws, second index for wsus or wsvs, depending on surface.
2093    ALLOCATE ( surfaces%mom_flux_tke(0:1,1:surfaces%ns) )
2094!
2095!-- Characteristic temperature and surface flux of sensible heat
2096    ALLOCATE ( surfaces%ts(1:surfaces%ns) )
2097    ALLOCATE ( surfaces%shf(1:surfaces%ns) )
2098!
2099!-- Surface temperature
2100    ALLOCATE ( surfaces%pt_surface(1:surfaces%ns) )
2101!
2102!-- Characteristic humidity and surface flux of latent heat
2103    IF ( humidity )  THEN
2104       ALLOCATE ( surfaces%qs(1:surfaces%ns) )
2105       ALLOCATE ( surfaces%qsws(1:surfaces%ns) )
2106       ALLOCATE ( surfaces%q_surface(1:surfaces%ns) )
2107       ALLOCATE ( surfaces%vpt_surface(1:surfaces%ns) )
2108    ENDIF
2109!
2110!-- Characteristic scalar and surface flux of scalar
2111    IF ( passive_scalar )  THEN
2112       ALLOCATE ( surfaces%ss(1:surfaces%ns) )
2113       ALLOCATE ( surfaces%ssws(1:surfaces%ns) )
2114    ENDIF
2115!
2116!-- Scaling parameter (cs*) and surface flux of chemical species
2117    IF ( air_chemistry )  THEN
2118       ALLOCATE ( surfaces%css(1:nvar,1:surfaces%ns) )
2119       ALLOCATE ( surfaces%cssws(1:nvar,1:surfaces%ns) )
2120    ENDIF
2121!
2122!-- Arrays for storing potential temperature and mixing ratio at first grid level
2123    ALLOCATE ( surfaces%pt1(1:surfaces%ns) )
2124    ALLOCATE ( surfaces%qv1(1:surfaces%ns) )
2125    ALLOCATE ( surfaces%vpt1(1:surfaces%ns) )
2126
2127    IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison)  THEN
2128       ALLOCATE ( surfaces%qcs(1:surfaces%ns) )
2129       ALLOCATE ( surfaces%ncs(1:surfaces%ns) )
2130       ALLOCATE ( surfaces%qcsws(1:surfaces%ns) )
2131       ALLOCATE ( surfaces%ncsws(1:surfaces%ns) )
2132    ENDIF
2133
2134    IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert)  THEN
2135       ALLOCATE ( surfaces%qrs(1:surfaces%ns) )
2136       ALLOCATE ( surfaces%nrs(1:surfaces%ns) )
2137       ALLOCATE ( surfaces%qrsws(1:surfaces%ns) )
2138       ALLOCATE ( surfaces%nrsws(1:surfaces%ns) )
2139    ENDIF
2140
2141    IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase)  THEN
2142       ALLOCATE ( surfaces%qis(1:surfaces%ns) )
2143       ALLOCATE ( surfaces%nis(1:surfaces%ns) )
2144       ALLOCATE ( surfaces%qisws(1:surfaces%ns) )
2145       ALLOCATE ( surfaces%nisws(1:surfaces%ns) )
2146    ENDIF
2147!
2148!-- Salinity surface flux
2149    IF ( ocean_mode )  ALLOCATE ( surfaces%sasws(1:surfaces%ns) )
2150
2151 END SUBROUTINE allocate_surface_attributes_v
2152
2153
2154!--------------------------------------------------------------------------------------------------!
2155! Description:
2156! ------------
2157!> Exit memory for vertical surface types.
2158!--------------------------------------------------------------------------------------------------!
2159#if defined( _OPENACC )
2160 SUBROUTINE exit_surface_attributes_v( surfaces )
2161
2162    IMPLICIT NONE
2163
2164    TYPE(surf_type) ::  surfaces  !< respective surface type
2165
2166    !$ACC EXIT DATA &
2167    !$ACC DELETE(surfaces%start_index(nys:nyn,nxl:nxr)) &
2168    !$ACC DELETE(surfaces%end_index(nys:nyn,nxl:nxr)) &
2169    !$ACC DELETE(surfaces%i(1:surfaces%ns)) &
2170    !$ACC DELETE(surfaces%j(1:surfaces%ns)) &
2171    !$ACC DELETE(surfaces%k(1:surfaces%ns)) &
2172    !$ACC DELETE(surfaces%uvw_abs(1:surfaces%ns)) &
2173    !$ACC DELETE(surfaces%ln_z_z0(1:surfaces%ns) ) &
2174    !$ACC DELETE(surfaces%ln_z_z0h(1:surfaces%ns) ) &
2175    !$ACC DELETE(surfaces%ln_z_z0q(1:surfaces%ns) ) &
2176    !$ACC DELETE(surfaces%z0(1:surfaces%ns)) &
2177    !$ACC DELETE(surfaces%z0h(1:surfaces%ns)) &
2178    !$ACC DELETE(surfaces%z0q(1:surfaces%ns)) &
2179    !$ACC DELETE(surfaces%rib(1:surfaces%ns)) &
2180    !$ACC DELETE(surfaces%mom_flux_uv(1:surfaces%ns)) &
2181    !$ACC DELETE(surfaces%mom_flux_w(1:surfaces%ns)) &
2182    !$ACC DELETE(surfaces%mom_flux_tke(0:1,1:surfaces%ns)) &
2183    !$ACC DELETE(surfaces%ts(1:surfaces%ns)) &
2184    !$ACC DELETE(surfaces%shf(1:surfaces%ns)) &
2185    !$ACC DELETE(surfaces%pt1(1:surfaces%ns)) &
2186    !$ACC DELETE(surfaces%qv1(1:surfaces%ns))
2187
2188 END SUBROUTINE exit_surface_attributes_v
2189#endif
2190
2191!--------------------------------------------------------------------------------------------------!
2192! Description:
2193! ------------
2194!> Enter memory for vertical surface types.
2195!--------------------------------------------------------------------------------------------------!
2196#if defined( _OPENACC )
2197 SUBROUTINE enter_surface_attributes_v( surfaces )
2198
2199    IMPLICIT NONE
2200
2201    TYPE(surf_type) ::  surfaces  !< respective surface type
2202
2203    !$ACC ENTER DATA &
2204    !$ACC COPYIN(surfaces%start_index(nys:nyn,nxl:nxr)) &
2205    !$ACC COPYIN(surfaces%end_index(nys:nyn,nxl:nxr)) &
2206    !$ACC COPYIN(surfaces%i(1:surfaces%ns)) &
2207    !$ACC COPYIN(surfaces%j(1:surfaces%ns)) &
2208    !$ACC COPYIN(surfaces%k(1:surfaces%ns)) &
2209    !$ACC COPYIN(surfaces%uvw_abs(1:surfaces%ns)) &
2210    !$ACC COPYIN(surfaces%ln_z_z0(1:surfaces%ns) ) &
2211    !$ACC COPYIN(surfaces%ln_z_z0h(1:surfaces%ns) ) &
2212    !$ACC COPYIN(surfaces%ln_z_z0q(1:surfaces%ns) ) &
2213    !$ACC COPYIN(surfaces%z0(1:surfaces%ns)) &
2214    !$ACC COPYIN(surfaces%z0h(1:surfaces%ns)) &
2215    !$ACC COPYIN(surfaces%z0q(1:surfaces%ns)) &
2216    !$ACC COPYIN(surfaces%rib(1:surfaces%ns)) &
2217    !$ACC COPYIN(surfaces%mom_flux_uv(1:surfaces%ns)) &
2218    !$ACC COPYIN(surfaces%mom_flux_w(1:surfaces%ns)) &
2219    !$ACC COPYIN(surfaces%mom_flux_tke(0:1,1:surfaces%ns)) &
2220    !$ACC COPYIN(surfaces%ts(1:surfaces%ns)) &
2221    !$ACC COPYIN(surfaces%shf(1:surfaces%ns)) &
2222    !$ACC COPYIN(surfaces%pt1(1:surfaces%ns)) &
2223    !$ACC COPYIN(surfaces%qv1(1:surfaces%ns))
2224
2225 END SUBROUTINE enter_surface_attributes_v
2226#endif
2227
2228!--------------------------------------------------------------------------------------------------!
2229! Description:
2230! ------------
2231!> Initialize surface elements, i.e. set initial values for surface fluxes, friction velocity,
2232!> calcuation of start/end indices, etc. Please note, further initialization concerning special
2233!> surface characteristics, e.g. soil- and vegatation type, building type, etc.,
2234!> is done in the land-surface and urban-surface module, respectively.
2235!--------------------------------------------------------------------------------------------------!
2236 SUBROUTINE init_surfaces
2237
2238    IMPLICIT NONE
2239
2240    INTEGER(iwp) ::  i  !< running index x-direction
2241    INTEGER(iwp) ::  j  !< running index y-direction
2242    INTEGER(iwp) ::  k  !< running index z-direction
2243    INTEGER(iwp) ::  kk !< auxiliary index z-direction
2244    INTEGER(iwp) ::  l  !< direction index
2245
2246
2247    INTEGER(iwp), DIMENSION(0:1)  ::  start_index_lsm_h !< dummy to determing local start index in surface type for given (j,i), for horizontal
2248                                                        !< natural surfaces
2249    INTEGER(iwp), DIMENSION(0:1)  ::  start_index_usm_h !< dummy to determing local start index in surface type for given (j,i), for horizontal
2250                                                        !< urban surfaces
2251    INTEGER(iwp), DIMENSION(0:1)  ::  num_lsm_h         !< current number of horizontal surface element, natural type
2252    INTEGER(iwp), DIMENSION(0:1)  ::  num_lsm_h_kji     !< dummy to determing local end index in surface type for given (j,i), for for horizonal
2253                                                        !< natural surfaces
2254    INTEGER(iwp), DIMENSION(0:1)  ::  num_usm_h         !< current number of horizontal surface element, urban type
2255    INTEGER(iwp), DIMENSION(0:1)  ::  num_usm_h_kji     !< dummy to determing local end index in surface type for given (j,i), for for horizonal urban
2256                                                        !< surfaces
2257
2258    INTEGER(iwp), DIMENSION(0:2) ::  num_def_h          !< current number of horizontal surface element, default type
2259    INTEGER(iwp), DIMENSION(0:2) ::  num_def_h_kji      !< dummy to determing local end index in surface type for given (j,i),
2260                                                        !< for horizonal default surfaces
2261    INTEGER(iwp), DIMENSION(0:2) ::  start_index_def_h  !< dummy to determing local start index in surface type for given (j,i),
2262                                                        !< for horizontal default surfaces
2263
2264    INTEGER(iwp), DIMENSION(0:3) ::  num_def_v          !< current number of vertical surface element, default type
2265    INTEGER(iwp), DIMENSION(0:3) ::  num_def_v_kji      !< dummy to determing local end index in surface type for given (j,i),
2266                                                        !< for vertical default surfaces
2267    INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v          !< current number of vertical surface element, natural type
2268    INTEGER(iwp), DIMENSION(0:3) ::  num_lsm_v_kji      !< dummy to determing local end index in surface type for given (j,i),
2269                                                        !< for vertical natural surfaces
2270    INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v          !< current number of vertical surface element, urban type
2271    INTEGER(iwp), DIMENSION(0:3) ::  num_usm_v_kji      !< dummy to determing local end index in surface type for given (j,i),
2272                                                        !< for vertical urban surfaces
2273
2274    INTEGER(iwp), DIMENSION(0:3) ::  start_index_def_v  !< dummy to determing local start index in surface type for given (j,i),
2275                                                        !< for vertical default surfaces
2276    INTEGER(iwp), DIMENSION(0:3) ::  start_index_lsm_v  !< dummy to determing local start index in surface type for given (j,i),
2277                                                        !< for vertical natural surfaces
2278    INTEGER(iwp), DIMENSION(0:3) ::  start_index_usm_v  !< dummy to determing local start index in surface type for given (j,i),
2279                                                        !< for vertical urban surfaces
2280
2281    LOGICAL ::  building                                !< flag indicating building grid point
2282    LOGICAL ::  terrain                                 !< flag indicating natural terrain grid point
2283    LOGICAL ::  unresolved_building                     !< flag indicating a grid point where actually a building is defined but not resolved by the
2284                                                        !< vertical grid
2285!
2286!-- Set offset indices, i.e. index difference between surface element and surface-bounded grid point.
2287!-- Upward facing - no horizontal offsets
2288    surf_def_h(0:2)%ioff = 0
2289    surf_def_h(0:2)%joff = 0
2290
2291    surf_lsm_h(0:1)%ioff = 0
2292    surf_lsm_h(0:1)%joff = 0
2293
2294    surf_usm_h(0:1)%ioff = 0
2295    surf_usm_h(0:1)%joff = 0
2296!
2297!-- Upward facing vertical offsets
2298    surf_def_h(0)%koff = -1
2299    surf_lsm_h(0)%koff = -1
2300    surf_usm_h(0)%koff = -1
2301!
2302!-- Downward facing vertical offset
2303    surf_def_h(1:2)%koff = 1
2304    surf_lsm_h(1)%koff   = 1
2305    surf_usm_h(1)%koff   = 1
2306!
2307!-- Vertical surfaces - no vertical offset
2308    surf_def_v(0:3)%koff = 0
2309    surf_lsm_v(0:3)%koff = 0
2310    surf_usm_v(0:3)%koff = 0
2311!
2312!-- North- and southward facing - no offset in x
2313    surf_def_v(0:1)%ioff = 0
2314    surf_lsm_v(0:1)%ioff = 0
2315    surf_usm_v(0:1)%ioff = 0
2316!
2317!-- Northward facing offset in y
2318    surf_def_v(0)%joff = -1
2319    surf_lsm_v(0)%joff = -1
2320    surf_usm_v(0)%joff = -1
2321!
2322!-- Southward facing offset in y
2323    surf_def_v(1)%joff = 1
2324    surf_lsm_v(1)%joff = 1
2325    surf_usm_v(1)%joff = 1
2326
2327!
2328!-- East- and westward facing - no offset in y
2329    surf_def_v(2:3)%joff = 0
2330    surf_lsm_v(2:3)%joff = 0
2331    surf_usm_v(2:3)%joff = 0
2332!
2333!-- Eastward facing offset in x
2334    surf_def_v(2)%ioff = -1
2335    surf_lsm_v(2)%ioff = -1
2336    surf_usm_v(2)%ioff = -1
2337!
2338!-- Westward facing offset in y
2339    surf_def_v(3)%ioff = 1
2340    surf_lsm_v(3)%ioff = 1
2341    surf_usm_v(3)%ioff = 1
2342
2343!
2344!-- Initialize surface attributes, store indicies, surfaces orientation, etc.,
2345    num_def_h(0:2) = 1
2346    num_def_v(0:3) = 1
2347
2348    num_lsm_h(0:1) = 1
2349    num_lsm_v(0:3) = 1
2350
2351    num_usm_h(0:1) = 1
2352    num_usm_v(0:3) = 1
2353
2354    start_index_def_h(0:2) = 1
2355    start_index_def_v(0:3) = 1
2356
2357    start_index_lsm_h(0:1) = 1
2358    start_index_lsm_v(0:3) = 1
2359
2360    start_index_usm_h(0:1) = 1
2361    start_index_usm_v(0:3) = 1
2362
2363    DO  i = nxl, nxr
2364       DO  j = nys, nyn
2365          num_def_h_kji = 0
2366          num_def_v_kji = 0
2367          num_lsm_h_kji = 0
2368          num_lsm_v_kji = 0
2369          num_usm_h_kji = 0
2370          num_usm_v_kji = 0
2371
2372          DO  k = nzb+1, nzt
2373!
2374!--          Check if current gridpoint belongs to the atmosphere
2375             IF ( BTEST( wall_flags_total_0(k,j,i), 0 ) )  THEN
2376!
2377!--             Check if grid point adjoins to any upward- and downward-facing horizontal surface,
2378!--             e.g. the Earth surface, plane roofs, or ceilings.
2379                DO kk = k-1, k+1, 2
2380!
2381!--                Check for top-fluxes first
2382                   IF ( kk == nzt+1  .AND.  use_top_fluxes )  THEN
2383                      CALL initialize_top( k, j, i, surf_def_h(2), num_def_h(2), num_def_h_kji(2) )
2384                   ELSE
2385!
2386!--                   set direction index of the potential surface
2387                      l = MERGE( 0, 1, kk == k-1 )
2388!
2389!--                   Upward- or donward facing surface. Distinguish between differet surface types.
2390!--                   To do, think about method to flag natural and non-natural surfaces.
2391                      IF ( .NOT. BTEST( wall_flags_total_0(kk,j,i), 0 ) )  THEN
2392!
2393!--                      Determine flags indicating terrain or building
2394                         terrain  = BTEST( wall_flags_total_0(kk,j,i), 5 )  .OR.  topo_no_distinct
2395                         building = BTEST( wall_flags_total_0(kk,j,i), 6 )  .OR.  topo_no_distinct
2396!
2397!--                      Unresolved_building indicates a surface with equal height as terrain but with a
2398!--                      non-grid resolved building on top. These surfaces will be flagged as urban
2399!--                      surfaces.
2400                         unresolved_building = BTEST( wall_flags_total_0(kk,j,i), 5 ) .AND.       &
2401                                               BTEST( wall_flags_total_0(kk,j,i), 6 )
2402!
2403!--                      Natural surface type
2404                         IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
2405                            CALL initialize_horizontal_surfaces( k, j, i, surf_lsm_h(l), num_lsm_h(l), &
2406                                                                 num_lsm_h_kji(l), .TRUE., .FALSE. )
2407!
2408!--                      Urban surface tpye
2409                         ELSEIF ( urban_surface  .AND.  building )  THEN
2410                            CALL initialize_horizontal_surfaces( k, j, i, surf_usm_h(l), num_usm_h(l), &
2411                                                                 num_usm_h_kji(l), .TRUE., .FALSE. )
2412!
2413!--                      Default surface type
2414                         ELSE
2415                            CALL initialize_horizontal_surfaces( k, j, i, surf_def_h(l), num_def_h(l), &
2416                                                                 num_def_h_kji(l), .TRUE., .FALSE. )
2417                         ENDIF
2418                      ENDIF
2419                   ENDIF
2420                ENDDO
2421!
2422!--             Check for vertical walls and, if required, initialize it.
2423!               Start with northward-facing surface.
2424                IF ( .NOT. BTEST( wall_flags_total_0(k,j-1,i), 0 ) )  THEN
2425!
2426!--                Determine flags indicating terrain or building
2427                   terrain  = BTEST( wall_flags_total_0(k,j-1,i), 5 )  .OR.  topo_no_distinct
2428                   building = BTEST( wall_flags_total_0(k,j-1,i), 6 )  .OR.  topo_no_distinct
2429
2430                   unresolved_building = BTEST( wall_flags_total_0(k,j-1,i), 5 )  .AND.            &
2431                                         BTEST( wall_flags_total_0(k,j-1,i), 6 )
2432
2433                   IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
2434                      CALL initialize_vertical_surfaces( k, j, i, surf_lsm_v(0), num_lsm_v(0),     &
2435                                                         num_lsm_v_kji(0), .FALSE., .FALSE.,       &
2436                                                         .FALSE., .TRUE. )
2437
2438                   ELSEIF ( urban_surface  .AND.  building )  THEN
2439                      CALL initialize_vertical_surfaces( k, j, i, surf_usm_v(0), num_usm_v(0),     &
2440                                                         num_usm_v_kji(0), .FALSE., .FALSE.,       &
2441                                                         .FALSE., .TRUE. )
2442                   ELSE
2443                      CALL initialize_vertical_surfaces( k, j, i, surf_def_v(0), num_def_v(0),     &
2444                                                         num_def_v_kji(0), .FALSE., .FALSE.,       &
2445                                                         .FALSE., .TRUE. )
2446                   ENDIF
2447                ENDIF
2448!
2449!--             Southward-facing surface
2450                IF ( .NOT. BTEST( wall_flags_total_0(k,j+1,i), 0 ) )  THEN
2451!
2452!--                Determine flags indicating terrain or building
2453                   terrain  = BTEST( wall_flags_total_0(k,j+1,i), 5 )  .OR.  topo_no_distinct
2454                   building = BTEST( wall_flags_total_0(k,j+1,i), 6 )  .OR.  topo_no_distinct
2455
2456                   unresolved_building = BTEST( wall_flags_total_0(k,j+1,i), 5 )  .AND.            &
2457                                         BTEST( wall_flags_total_0(k,j+1,i), 6 )
2458
2459                   IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
2460                      CALL initialize_vertical_surfaces( k, j, i, surf_lsm_v(1), num_lsm_v(1),     &
2461                                                         num_lsm_v_kji(1), .FALSE., .FALSE.,       &
2462                                                         .TRUE., .FALSE. )
2463
2464                   ELSEIF ( urban_surface  .AND.  building )  THEN
2465                      CALL initialize_vertical_surfaces( k, j, i, surf_usm_v(1), num_usm_v(1),     &
2466                                                         num_usm_v_kji(1), .FALSE., .FALSE.,       &
2467                                                         .TRUE., .FALSE. )
2468                   ELSE
2469                      CALL initialize_vertical_surfaces( k, j, i, surf_def_v(1), num_def_v(1),     &
2470                                                         num_def_v_kji(1), .FALSE., .FALSE.,       &
2471                                                         .TRUE., .FALSE. )
2472                   ENDIF
2473                ENDIF
2474!
2475!--             Eastward-facing surface
2476                IF ( .NOT. BTEST( wall_flags_total_0(k,j,i-1), 0 ) )  THEN
2477!
2478!--                Determine flags indicating terrain or building
2479                   terrain  = BTEST( wall_flags_total_0(k,j,i-1), 5 )  .OR.  topo_no_distinct
2480                   building = BTEST( wall_flags_total_0(k,j,i-1), 6 )  .OR.  topo_no_distinct
2481
2482                   unresolved_building = BTEST( wall_flags_total_0(k,j,i-1), 5 )  .AND.            &
2483                                         BTEST( wall_flags_total_0(k,j,i-1), 6 )
2484
2485                   IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
2486                      CALL initialize_vertical_surfaces( k, j, i, surf_lsm_v(2), num_lsm_v(2),     &
2487                                                         num_lsm_v_kji(2), .TRUE., .FALSE.,        &
2488                                                         .FALSE., .FALSE. )
2489
2490                   ELSEIF ( urban_surface  .AND.  building )  THEN
2491                      CALL initialize_vertical_surfaces( k, j, i, surf_usm_v(2), num_usm_v(2),     &
2492                                                         num_usm_v_kji(2), .TRUE., .FALSE.,        &
2493                                                         .FALSE., .FALSE. )
2494                   ELSE
2495                      CALL initialize_vertical_surfaces( k, j, i, surf_def_v(2), num_def_v(2),     &
2496                                                         num_def_v_kji(2), .TRUE., .FALSE.,        &
2497                                                         .FALSE., .FALSE. )
2498                   ENDIF
2499                ENDIF
2500!
2501!--             Westward-facing surface
2502                IF ( .NOT. BTEST( wall_flags_total_0(k,j,i+1), 0 ) )  THEN
2503!
2504!--                Determine flags indicating terrain or building
2505                   terrain  = BTEST( wall_flags_total_0(k,j,i+1), 5 )  .OR.  topo_no_distinct
2506                   building = BTEST( wall_flags_total_0(k,j,i+1), 6 )  .OR.  topo_no_distinct
2507
2508                   unresolved_building = BTEST( wall_flags_total_0(k,j,i+1), 5 )  .AND.            &
2509                                         BTEST( wall_flags_total_0(k,j,i+1), 6 )
2510
2511                   IF ( land_surface  .AND.  terrain  .AND.  .NOT. unresolved_building )  THEN
2512                      CALL initialize_vertical_surfaces( k, j, i, surf_lsm_v(3), num_lsm_v(3),     &
2513                                                         num_lsm_v_kji(3), .FALSE., .TRUE.,        &
2514                                                        .FALSE., .FALSE. )
2515
2516                   ELSEIF ( urban_surface  .AND.  building )  THEN
2517                      CALL initialize_vertical_surfaces( k, j, i, surf_usm_v(3), num_usm_v(3),     &
2518                                                         num_usm_v_kji(3), .FALSE., .TRUE.,        &
2519                                                        .FALSE., .FALSE. )
2520                   ELSE
2521                      CALL initialize_vertical_surfaces( k, j, i, surf_def_v(3), num_def_v(3),     &
2522                                                         num_def_v_kji(3), .FALSE., .TRUE.,        &
2523                                                        .FALSE., .FALSE. )
2524                   ENDIF
2525                ENDIF
2526             ENDIF
2527
2528
2529          ENDDO
2530!
2531!--       Determine start- and end-index at grid point (j,i). Also, for horizontal surfaces more
2532!--       than 1 horizontal surface element can exist at grid point (j,i) if overhanging structures
2533!--       are present.
2534!--       Upward-facing surfaces
2535          surf_def_h(0)%start_index(j,i) = start_index_def_h(0)
2536          surf_def_h(0)%end_index(j,i)   = surf_def_h(0)%start_index(j,i) + num_def_h_kji(0) - 1
2537          start_index_def_h(0)           = surf_def_h(0)%end_index(j,i) + 1
2538!
2539!--       ATTENTION:
2540!--       Workaround to prevent vectorization bug on NEC Aurora
2541          IF ( start_index_def_h(0) < -99999 )  THEN
2542             PRINT*, 'i=', i, ' j=',j, ' s=',surf_def_h(0)%start_index(j,i),                       &
2543                    ' e=', surf_def_h(0)%end_index(j,i)
2544          ENDIF
2545!
2546!--       Downward-facing surfaces, except model top
2547          surf_def_h(1)%start_index(j,i) = start_index_def_h(1)
2548          surf_def_h(1)%end_index(j,i)   = surf_def_h(1)%start_index(j,i) + num_def_h_kji(1) - 1
2549          start_index_def_h(1)           = surf_def_h(1)%end_index(j,i) + 1
2550!
2551!--       Downward-facing surfaces -- model top fluxes
2552          surf_def_h(2)%start_index(j,i) = start_index_def_h(2)
2553          surf_def_h(2)%end_index(j,i)   = surf_def_h(2)%start_index(j,i) + num_def_h_kji(2) - 1
2554          start_index_def_h(2)           = surf_def_h(2)%end_index(j,i) + 1
2555!
2556!--       Upward- and downward-facing horizontal land and urban surfaces
2557          DO l = 0, 1
2558!
2559!--          Horizontal natural land surfaces
2560             surf_lsm_h(l)%start_index(j,i) = start_index_lsm_h(l)
2561             surf_lsm_h(l)%end_index(j,i)   = surf_lsm_h(l)%start_index(j,i) + num_lsm_h_kji(l) - 1
2562             start_index_lsm_h(l)           = surf_lsm_h(l)%end_index(j,i) + 1
2563!
2564!--          Horizontal urban surfaces
2565             surf_usm_h(l)%start_index(j,i) = start_index_usm_h(l)
2566             surf_usm_h(l)%end_index(j,i)   = surf_usm_h(l)%start_index(j,i) + num_usm_h_kji(l) - 1
2567             start_index_usm_h(l)           = surf_usm_h(l)%end_index(j,i) + 1
2568          ENDDO
2569
2570!
2571!--       Vertical surfaces - Default type
2572          surf_def_v(0)%start_index(j,i) = start_index_def_v(0)
2573          surf_def_v(1)%start_index(j,i) = start_index_def_v(1)
2574          surf_def_v(2)%start_index(j,i) = start_index_def_v(2)
2575          surf_def_v(3)%start_index(j,i) = start_index_def_v(3)
2576          surf_def_v(0)%end_index(j,i)   = start_index_def_v(0) + num_def_v_kji(0) - 1
2577          surf_def_v(1)%end_index(j,i)   = start_index_def_v(1) + num_def_v_kji(1) - 1
2578          surf_def_v(2)%end_index(j,i)   = start_index_def_v(2) + num_def_v_kji(2) - 1
2579          surf_def_v(3)%end_index(j,i)   = start_index_def_v(3) + num_def_v_kji(3) - 1
2580          start_index_def_v(0)           = surf_def_v(0)%end_index(j,i) + 1
2581          start_index_def_v(1)           = surf_def_v(1)%end_index(j,i) + 1
2582          start_index_def_v(2)           = surf_def_v(2)%end_index(j,i) + 1
2583          start_index_def_v(3)           = surf_def_v(3)%end_index(j,i) + 1
2584!
2585!--       Natural type
2586          surf_lsm_v(0)%start_index(j,i) = start_index_lsm_v(0)
2587          surf_lsm_v(1)%start_index(j,i) = start_index_lsm_v(1)
2588          surf_lsm_v(2)%start_index(j,i) = start_index_lsm_v(2)
2589          surf_lsm_v(3)%start_index(j,i) = start_index_lsm_v(3)
2590          surf_lsm_v(0)%end_index(j,i)   = start_index_lsm_v(0) + num_lsm_v_kji(0) - 1
2591          surf_lsm_v(1)%end_index(j,i)   = start_index_lsm_v(1) + num_lsm_v_kji(1) - 1
2592          surf_lsm_v(2)%end_index(j,i)   = start_index_lsm_v(2) + num_lsm_v_kji(2) - 1
2593          surf_lsm_v(3)%end_index(j,i)   = start_index_lsm_v(3) + num_lsm_v_kji(3) - 1
2594          start_index_lsm_v(0)           = surf_lsm_v(0)%end_index(j,i) + 1
2595          start_index_lsm_v(1)           = surf_lsm_v(1)%end_index(j,i) + 1
2596          start_index_lsm_v(2)           = surf_lsm_v(2)%end_index(j,i) + 1
2597          start_index_lsm_v(3)           = surf_lsm_v(3)%end_index(j,i) + 1
2598!
2599!--       Urban type
2600          surf_usm_v(0)%start_index(j,i) = start_index_usm_v(0)
2601          surf_usm_v(1)%start_index(j,i) = start_index_usm_v(1)
2602          surf_usm_v(2)%start_index(j,i) = start_index_usm_v(2)
2603          surf_usm_v(3)%start_index(j,i) = start_index_usm_v(3)
2604          surf_usm_v(0)%end_index(j,i)   = start_index_usm_v(0) + num_usm_v_kji(0) - 1
2605          surf_usm_v(1)%end_index(j,i)   = start_index_usm_v(1) + num_usm_v_kji(1) - 1
2606          surf_usm_v(2)%end_index(j,i)   = start_index_usm_v(2) + num_usm_v_kji(2) - 1
2607          surf_usm_v(3)%end_index(j,i)   = start_index_usm_v(3) + num_usm_v_kji(3) - 1
2608          start_index_usm_v(0)           = surf_usm_v(0)%end_index(j,i) + 1
2609          start_index_usm_v(1)           = surf_usm_v(1)%end_index(j,i) + 1
2610          start_index_usm_v(2)           = surf_usm_v(2)%end_index(j,i) + 1
2611          start_index_usm_v(3)           = surf_usm_v(3)%end_index(j,i) + 1
2612
2613
2614       ENDDO
2615    ENDDO
2616
2617 CONTAINS
2618
2619!--------------------------------------------------------------------------------------------------!
2620! Description:
2621! ------------
2622!> Initialize horizontal surface elements, upward- and downward-facing. Note, horizontal surface
2623!> type also comprises model-top fluxes, which are, initialized in a different routine.
2624!--------------------------------------------------------------------------------------------------!
2625 SUBROUTINE initialize_horizontal_surfaces( k, j, i, surf, num_h, num_h_kji, upward_facing,        &
2626                                            downward_facing )
2627
2628    IMPLICIT NONE
2629
2630    INTEGER(iwp)  ::  i          !< running index x-direction
2631    INTEGER(iwp)  ::  j          !< running index y-direction
2632    INTEGER(iwp)  ::  k          !< running index z-direction
2633    INTEGER(iwp)  ::  num_h      !< current number of surface element
2634    INTEGER(iwp)  ::  num_h_kji  !< dummy increment
2635    INTEGER(iwp)  ::  lsp        !< running index chemical species
2636    INTEGER(iwp)  ::  lsp_pr     !< running index chemical species??
2637
2638    LOGICAL       ::  upward_facing    !< flag indicating upward-facing surface
2639    LOGICAL       ::  downward_facing  !< flag indicating downward-facing surface
2640
2641    TYPE(surf_type) ::  surf  !< respective surface type
2642
2643!
2644!-- Store indices of respective surface element
2645    surf%i(num_h) = i
2646    surf%j(num_h) = j
2647    surf%k(num_h) = k
2648!
2649!-- Surface orientation, bit 0 is set to 1 for upward-facing surfaces, bit 1 is for downward-facing
2650!-- surfaces.
2651    IF ( upward_facing   )  surf%facing(num_h) = IBSET( surf%facing(num_h), 0 )
2652    IF ( downward_facing )  surf%facing(num_h) = IBSET( surf%facing(num_h), 1 )
2653!
2654!-- Initialize surface-layer height
2655    IF ( upward_facing )  THEN
2656       surf%z_mo(num_h) = zu(k) - zw(k-1)
2657    ELSE
2658       surf%z_mo(num_h) = zw(k) - zu(k)
2659    ENDIF
2660
2661    surf%z0(num_h)  = roughness_length
2662    surf%z0h(num_h) = z0h_factor * roughness_length
2663    surf%z0q(num_h) = z0h_factor * roughness_length
2664!
2665!-- Initialization in case of 1D pre-cursor run
2666    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
2667       IF ( .NOT. constant_diffusion )  THEN
2668          IF ( constant_flux_layer )  THEN
2669             surf%ol(num_h)   = surf%z_mo(num_h) / ( ri1d(nzb+1) + 1.0E-20_wp )
2670             surf%us(num_h)   = us1d
2671             surf%usws(num_h) = usws1d
2672             surf%vsws(num_h) = vsws1d
2673          ELSE
2674             surf%ol(num_h)   = surf%z_mo(num_h) / zeta_min
2675             surf%us(num_h)   = 0.0_wp
2676             surf%usws(num_h) = 0.0_wp
2677             surf%vsws(num_h) = 0.0_wp
2678          ENDIF
2679       ELSE
2680          surf%ol(num_h)   = surf%z_mo(num_h) / zeta_min
2681          surf%us(num_h)   = 0.0_wp
2682          surf%usws(num_h) = 0.0_wp
2683          surf%vsws(num_h) = 0.0_wp
2684       ENDIF
2685!
2686!-- Initialization in all other cases
2687    ELSE
2688
2689       surf%ol(num_h) = surf%z_mo(num_h) / zeta_min
2690!
2691!--    Very small number is required for calculation of Obukhov length at first timestep
2692       surf%us(num_h)   = 1E-30_wp
2693       surf%usws(num_h) = 0.0_wp
2694       surf%vsws(num_h) = 0.0_wp
2695
2696    ENDIF
2697
2698    surf%rib(num_h)     = 0.0_wp
2699    surf%uvw_abs(num_h) = 0.0_wp
2700!
2701!-- Initialize ln(z/z0)
2702    surf%ln_z_z0(num_h)  = LOG( surf%z_mo(num_h) / surf%z0(num_h) )
2703    surf%ln_z_z0h(num_h) = LOG( surf%z_mo(num_h) / surf%z0h(num_h) )
2704    surf%ln_z_z0q(num_h) = LOG( surf%z_mo(num_h) / surf%z0q(num_h) )
2705
2706    IF ( .NOT. constant_diffusion )  THEN
2707       surf%u_0(num_h) = 0.0_wp
2708       surf%v_0(num_h) = 0.0_wp
2709    ENDIF
2710
2711    surf%ts(num_h) = 0.0_wp
2712!
2713!-- Set initial value for surface temperature
2714    surf%pt_surface(num_h) = pt_surface
2715
2716    IF ( humidity )  THEN
2717       surf%qs(num_h)   = 0.0_wp
2718       IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison)  THEN
2719          surf%qcs(num_h) = 0.0_wp
2720          surf%ncs(num_h) = 0.0_wp
2721
2722          surf%qcsws(num_h) = 0.0_wp
2723          surf%ncsws(num_h) = 0.0_wp
2724
2725       ENDIF
2726       IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert)  THEN
2727          surf%qrs(num_h) = 0.0_wp
2728          surf%nrs(num_h) = 0.0_wp
2729
2730          surf%qrsws(num_h) = 0.0_wp
2731          surf%nrsws(num_h) = 0.0_wp
2732
2733          surf%pt1(num_h)  = 0.0_wp
2734          surf%qv1(num_h)  = 0.0_wp
2735          surf%vpt1(num_h) = 0.0_wp
2736
2737       ENDIF
2738
2739       IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase)  THEN
2740          surf%qis(num_h) = 0.0_wp
2741          surf%nis(num_h) = 0.0_wp
2742
2743          surf%qisws(num_h) = 0.0_wp
2744          surf%nisws(num_h) = 0.0_wp
2745       ENDIF
2746
2747
2748       surf%q_surface(num_h)   = q_surface
2749       surf%vpt_surface(num_h) = surf%pt_surface(num_h) *                                          &
2750                                ( 1.0_wp + 0.61_wp * surf%q_surface(num_h) )
2751    ENDIF
2752
2753    IF ( passive_scalar )  surf%ss(num_h) = 0.0_wp
2754
2755    DO  lsp = 1, nvar
2756       IF ( air_chemistry )  surf%css(lsp,num_h)   = 0.0_wp
2757!
2758!--    Ensure that fluxes of compounds which are not specified in namelist are all zero
2759!--    --> kanani: revise
2760       IF ( air_chemistry )  surf%cssws(lsp,num_h) = 0.0_wp
2761    ENDDO
2762!
2763!-- Inititalize surface fluxes of sensible and latent heat, as well as passive scalar
2764    IF ( use_surface_fluxes )  THEN
2765
2766       IF ( upward_facing )  THEN
2767          IF ( constant_heatflux )  THEN
2768!
2769!--          Initialize surface heatflux. However, skip this for now if random_heatflux is set.
2770!--          This case, shf is initialized later.
2771             IF ( .NOT. random_heatflux )  THEN
2772                surf%shf(num_h) = surface_heatflux * heatflux_input_conversion(k-1)
2773!
2774!--             Check if surface heat flux might be replaced by prescribed wall heatflux
2775                IF ( k-1 /= 0 )  THEN
2776                   surf%shf(num_h) = wall_heatflux(0) * heatflux_input_conversion(k-1)
2777                ENDIF
2778             ENDIF
2779          ELSE
2780             surf%shf(num_h) = 0.0_wp
2781          ENDIF
2782!
2783!--    Set heat-flux at downward-facing surfaces
2784       ELSE
2785          surf%shf(num_h) = wall_heatflux(5) * heatflux_input_conversion(k)
2786       ENDIF
2787
2788       IF ( humidity )  THEN
2789          IF ( upward_facing )  THEN
2790             IF ( constant_waterflux )  THEN
2791                surf%qsws(num_h) = surface_waterflux * waterflux_input_conversion(k-1)
2792                IF ( k-1 /= 0 )  THEN
2793                   surf%qsws(num_h) = wall_humidityflux(0) * waterflux_input_conversion(k-1)
2794                ENDIF
2795             ELSE
2796                surf%qsws(num_h) = 0.0_wp
2797             ENDIF
2798          ELSE
2799             surf%qsws(num_h) = wall_humidityflux(5) * waterflux_input_conversion(k)
2800          ENDIF
2801       ENDIF
2802
2803       IF ( passive_scalar )  THEN
2804          IF ( upward_facing )  THEN
2805             IF ( constant_scalarflux )  THEN
2806                surf%ssws(num_h) = surface_scalarflux  * rho_air_zw(k-1)
2807
2808                IF ( k-1 /= 0 )  surf%ssws(num_h) = wall_scalarflux(0) * rho_air_zw(k-1)
2809             ELSE
2810                surf%ssws(num_h) = 0.0_wp
2811             ENDIF
2812          ELSE
2813             surf%ssws(num_h) = wall_scalarflux(5) * rho_air_zw(k)
2814          ENDIF
2815       ENDIF
2816
2817       IF ( air_chemistry )  THEN
2818          lsp_pr = 1
2819          DO  WHILE ( TRIM( surface_csflux_name( lsp_pr ) ) /= 'novalue' ) !<'novalue' is the default
2820             DO  lsp = 1, nvar
2821!
2822!--             Assign surface flux for each variable species
2823                IF ( TRIM( spc_names(lsp) ) == TRIM( surface_csflux_name(lsp_pr) ) )  THEN
2824                   IF ( upward_facing )  THEN
2825                      IF ( constant_csflux(lsp_pr) )  THEN
2826                         surf%cssws(lsp,num_h) = surface_csflux(lsp_pr) * rho_air_zw(k-1)
2827
2828                         IF ( k-1 /= 0 )  surf%cssws(lsp,num_h) = wall_csflux(lsp,0) *             &
2829                                                                  rho_air_zw(k-1)
2830                      ELSE
2831                         surf%cssws(lsp,num_h) = 0.0_wp
2832                      ENDIF
2833                   ELSE
2834                      surf%cssws(lsp,num_h) = wall_csflux(lsp,5) * rho_air_zw(k)
2835                   ENDIF
2836                ENDIF
2837             ENDDO
2838             lsp_pr = lsp_pr + 1
2839          ENDDO
2840       ENDIF
2841
2842       IF ( ocean_mode )  THEN
2843          IF ( upward_facing )  THEN
2844             surf%sasws(num_h) = bottom_salinityflux * rho_air_zw(k-1)
2845          ELSE
2846             surf%sasws(num_h) = 0.0_wp
2847          ENDIF
2848       ENDIF
2849    ENDIF
2850!
2851!-- Increment surface indices
2852    num_h     = num_h + 1
2853    num_h_kji = num_h_kji + 1
2854
2855
2856 END SUBROUTINE initialize_horizontal_surfaces
2857
2858
2859!--------------------------------------------------------------------------------------------------!
2860! Description:
2861! ------------
2862!> Initialize model-top fluxes. Currently, only the heatflux and salinity flux can be prescribed,
2863!> latent flux is zero in this case!
2864!--------------------------------------------------------------------------------------------------!
2865 SUBROUTINE initialize_top( k, j, i, surf, num_h, num_h_kji )
2866
2867    IMPLICIT NONE
2868
2869    INTEGER(iwp)  ::  i          !< running index x-direction
2870    INTEGER(iwp)  ::  j          !< running index y-direction
2871    INTEGER(iwp)  ::  k          !< running index z-direction
2872    INTEGER(iwp)  ::  num_h      !< current number of surface element
2873    INTEGER(iwp)  ::  num_h_kji  !< dummy increment
2874    INTEGER(iwp)  ::  lsp        !< running index for chemical species
2875
2876    TYPE( surf_type ) ::  surf   !< respective surface type
2877!
2878!-- Store indices of respective surface element
2879    surf%i(num_h) = i
2880    surf%j(num_h) = j
2881    surf%k(num_h) = k
2882!
2883!-- Initialize top heat flux
2884    IF ( constant_top_heatflux )  surf%shf(num_h) = top_heatflux * heatflux_input_conversion(nzt+1)
2885!
2886!-- Initialization in case of a coupled model run
2887    IF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
2888       surf%shf(num_h) = 0.0_wp
2889       surf%qsws(num_h) = 0.0_wp
2890    ENDIF
2891!
2892!-- Prescribe latent heat flux at the top
2893    IF ( humidity )  THEN
2894       surf%qsws(num_h) = 0.0_wp
2895       IF ( surf_bulk_cloud_model  .AND.  surf_microphysics_morrison )  THEN
2896          surf%ncsws(num_h) = 0.0_wp
2897          surf%qcsws(num_h) = 0.0_wp
2898       ENDIF
2899       IF ( surf_bulk_cloud_model  .AND.  surf_microphysics_seifert )  THEN
2900          surf%nrsws(num_h) = 0.0_wp
2901          surf%qrsws(num_h) = 0.0_wp
2902       ENDIF
2903       IF ( surf_bulk_cloud_model  .AND.  surf_microphysics_ice_phase )  THEN
2904          surf%nisws(num_h) = 0.0_wp
2905          surf%qisws(num_h) = 0.0_wp
2906       ENDIF
2907    ENDIF
2908!
2909!-- Prescribe top scalar flux
2910    IF ( passive_scalar .AND. constant_top_scalarflux )  surf%ssws(num_h) = top_scalarflux *       &
2911                                                                            rho_air_zw(nzt+1)
2912!
2913!-- Prescribe top chemical species' flux
2914    DO  lsp = 1, nvar
2915       IF ( air_chemistry  .AND.  constant_top_csflux(lsp) )  THEN
2916          surf%cssws(lsp,num_h) = top_csflux(lsp) * rho_air_zw(nzt+1)
2917       ENDIF
2918    ENDDO
2919!
2920!-- Prescribe top salinity flux
2921    IF ( ocean_mode .AND. constant_top_salinityflux)  surf%sasws(num_h) = top_salinityflux *       &
2922                                                                          rho_air_zw(nzt+1)
2923!
2924!-- Top momentum fluxes
2925    IF ( constant_top_momentumflux )  THEN
2926       surf%usws(num_h) = top_momentumflux_u * momentumflux_input_conversion(nzt+1)
2927       surf%vsws(num_h) = top_momentumflux_v * momentumflux_input_conversion(nzt+1)
2928    ENDIF
2929!
2930!-- Increment surface indices
2931    num_h     = num_h + 1
2932    num_h_kji = num_h_kji + 1
2933
2934
2935 END SUBROUTINE initialize_top
2936
2937
2938!--------------------------------------------------------------------------------------------------!
2939! Description:
2940! ------------
2941!> Initialize vertical surface elements.
2942!--------------------------------------------------------------------------------------------------!
2943 SUBROUTINE initialize_vertical_surfaces( k, j, i, surf, num_v, num_v_kji, east_facing,            &
2944                                          west_facing, south_facing, north_facing )
2945
2946    IMPLICIT NONE
2947
2948    INTEGER(iwp) ::  component  !< index of wall_fluxes_ array for respective orientation
2949    INTEGER(iwp) ::  i          !< running index x-direction
2950    INTEGER(iwp) ::  j          !< running index x-direction
2951    INTEGER(iwp) ::  k          !< running index x-direction
2952    INTEGER(iwp) ::  num_v      !< current number of surface element
2953    INTEGER(iwp) ::  num_v_kji  !< current number of surface element at (j,i)
2954    INTEGER(iwp) ::  lsp        !< running index for chemical species
2955
2956
2957    LOGICAL ::  east_facing   !< flag indicating east-facing surfaces
2958    LOGICAL ::  north_facing  !< flag indicating north-facing surfaces
2959    LOGICAL ::  south_facing  !< flag indicating south-facing surfaces
2960    LOGICAL ::  west_facing   !< flag indicating west-facing surfaces
2961
2962    TYPE( surf_type ) ::  surf  !< respective surface type
2963
2964!
2965!-- Store indices of respective wall element
2966    surf%i(num_v) = i
2967    surf%j(num_v) = j
2968    surf%k(num_v) = k
2969!
2970!-- Initialize surface-layer height, or more precisely, distance to surface
2971    IF ( north_facing  .OR.  south_facing )  THEN
2972       surf%z_mo(num_v) = 0.5_wp * dy
2973    ELSE
2974       surf%z_mo(num_v) = 0.5_wp * dx
2975    ENDIF
2976
2977    surf%facing(num_v) = 0
2978!
2979!-- Surface orientation. Moreover, set component id to map wall_heatflux, etc., on surface type
2980!-- (further below)
2981    IF ( north_facing )  THEN
2982       surf%facing(num_v) = 5 !IBSET( surf%facing(num_v), 0 )
2983       component          = 4
2984    ENDIF
2985
2986    IF ( south_facing )  THEN
2987       surf%facing(num_v) = 6 !IBSET( surf%facing(num_v), 1 )
2988       component          = 3
2989    ENDIF
2990
2991    IF ( east_facing )  THEN
2992       surf%facing(num_v) = 7 !IBSET( surf%facing(num_v), 2 )
2993       component          = 2
2994    ENDIF
2995
2996    IF ( west_facing )  THEN
2997       surf%facing(num_v) = 8 !IBSET( surf%facing(num_v), 3 )
2998       component          = 1
2999    ENDIF
3000
3001
3002    surf%z0(num_v)  = roughness_length
3003    surf%z0h(num_v) = z0h_factor * roughness_length
3004    surf%z0q(num_v) = z0h_factor * roughness_length
3005
3006    surf%us(num_v)  = 0.0_wp
3007!
3008!-- Initialize ln(z/z0)
3009    surf%ln_z_z0(num_v)  = LOG( surf%z_mo(num_v) / surf%z0(num_v)  )
3010    surf%ln_z_z0h(num_v) = LOG( surf%z_mo(num_v) / surf%z0h(num_v) )
3011    surf%ln_z_z0q(num_v) = LOG( surf%z_mo(num_v) / surf%z0q(num_v) )
3012!
3013!-- If required, initialize Obukhov length
3014    IF ( ALLOCATED( surf%ol ) )  surf%ol(num_v) = surf%z_mo(num_v) / zeta_min
3015
3016    surf%uvw_abs(num_v) = 0.0_wp
3017    surf%mom_flux_uv(num_v) = 0.0_wp
3018    surf%mom_flux_w(num_v) = 0.0_wp
3019    surf%mom_flux_tke(0:1,num_v) = 0.0_wp
3020
3021    surf%ts(num_v)  = 0.0_wp
3022    surf%shf(num_v) = wall_heatflux(component)
3023!
3024!-- Set initial value for surface temperature
3025    surf%pt_surface(num_v) = pt_surface
3026
3027    IF ( humidity )  THEN
3028       surf%qs(num_v) = 0.0_wp
3029       surf%qsws(num_v) = wall_humidityflux(component)
3030!
3031!--    Following wall fluxes are assumed to be zero
3032       IF ( surf_bulk_cloud_model .AND. surf_microphysics_morrison)  THEN
3033          surf%qcs(num_v) = 0.0_wp
3034          surf%ncs(num_v) = 0.0_wp
3035          surf%qcsws(num_v) = 0.0_wp
3036          surf%ncsws(num_v) = 0.0_wp
3037       ENDIF
3038       IF ( surf_bulk_cloud_model .AND. surf_microphysics_seifert)  THEN
3039          surf%qrs(num_v) = 0.0_wp
3040          surf%nrs(num_v) = 0.0_wp
3041          surf%qrsws(num_v) = 0.0_wp
3042          surf%nrsws(num_v) = 0.0_wp
3043       ENDIF
3044       IF ( surf_bulk_cloud_model .AND. surf_microphysics_ice_phase)  THEN
3045          surf%qis(num_v) = 0.0_wp
3046          surf%nis(num_v) = 0.0_wp
3047          surf%qisws(num_v) = 0.0_wp
3048          surf%nisws(num_v) = 0.0_wp
3049       ENDIF
3050    ENDIF
3051
3052    IF ( passive_scalar )  THEN
3053       surf%ss(num_v) = 0.0_wp
3054       surf%ssws(num_v) = wall_scalarflux(component)
3055    ENDIF
3056
3057    IF ( air_chemistry )  THEN
3058       DO  lsp = 1, nvar
3059          surf%css(lsp,num_v) = 0.0_wp
3060          surf%cssws(lsp,num_v) = wall_csflux(lsp,component)
3061       ENDDO
3062    ENDIF
3063
3064!
3065!-- So far, salinityflux at vertical surfaces is simply zero at the moment
3066    IF ( ocean_mode )  surf%sasws(num_v) = wall_salinityflux(component)
3067!
3068!-- Increment wall indices
3069    num_v     = num_v + 1
3070    num_v_kji = num_v_kji + 1
3071
3072 END SUBROUTINE initialize_vertical_surfaces
3073
3074 END SUBROUTINE init_surfaces
3075
3076!--------------------------------------------------------------------------------------------------!
3077! Description:
3078! ------------
3079!> Initialize single surface properties from 2D input arrays
3080!--------------------------------------------------------------------------------------------------!
3081 SUBROUTINE init_single_surface_properties( var_surf, var_2d, ns, fill_value, index_space_i,       &
3082                                            index_space_j )
3083
3084    INTEGER(iwp) ::  m   !< running index over surface elements
3085    INTEGER(iwp) ::  ns  !< number of surface elements in var_surf
3086
3087    INTEGER(iwp), DIMENSION(1:ns) ::  index_space_i  !< grid indices along x direction where surface properties should be defined
3088    INTEGER(iwp), DIMENSION(1:ns) ::  index_space_j  !< grid indices along y direction where surface properties should be defined
3089
3090    REAL(wp) ::  fill_value !< fill value in var_2d
3091
3092    REAL(wp), DIMENSION(1:ns) ::  var_surf  !< 1D surface variable that should be initialized
3093    REAL(wp), DIMENSION(nys:nyn,nxl:nxr) ::  var_2d  !< input variable
3094
3095    DO  m = 1, ns
3096       IF ( var_2d(index_space_j(m),index_space_i(m)) /= fill_value )  THEN
3097          var_surf(m) = var_2d(index_space_j(m),index_space_i(m))
3098       ENDIF
3099    ENDDO
3100
3101 END SUBROUTINE init_single_surface_properties
3102
3103!--------------------------------------------------------------------------------------------------!
3104! Description:
3105! ------------
3106!> Gathers all surface elements with the same facing (but possibly different type) onto a surface
3107!> type, and writes binary data into restart files.
3108!--------------------------------------------------------------------------------------------------!
3109 SUBROUTINE surface_wrd_local
3110
3111
3112    IMPLICIT NONE
3113
3114    CHARACTER(LEN=1)             ::  dum            !< dummy string to create output-variable name
3115
3116    INTEGER(iwp)                 ::  i              !< running index x-direction
3117    INTEGER(iwp)                 ::  j              !< running index y-direction
3118    INTEGER(iwp)                 ::  l              !< index surface type orientation
3119    INTEGER(iwp)                 ::  lsp            !< running index chemical species
3120    INTEGER(iwp)                 ::  m              !< running index for surface elements on individual surface array
3121    INTEGER(iwp), DIMENSION(0:2) ::  start_index_h  !< start index for horizontal surface elements on gathered surface array
3122    INTEGER(iwp), DIMENSION(0:3) ::  mm             !< running index for surface elements on gathered surface array
3123    INTEGER(iwp), DIMENSION(0:3) ::  start_index_v  !< start index for vertical surface elements on gathered surface array
3124
3125    INTEGER(iwp),DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index  !< index for surface data (MPI-IO)
3126
3127    LOGICAL ::  surface_data_to_write  !< switch for MPI-I/O if PE has surface data to write
3128
3129    TYPE(surf_type), DIMENSION(0:2) ::  surf_h  !< gathered horizontal surfaces, contains all surface types
3130    TYPE(surf_type), DIMENSION(0:3) ::  surf_v  !< gathered vertical surfaces, contains all surface types
3131
3132!
3133!-- Determine total number of horizontal and vertical surface elements before writing var_list
3134    CALL surface_last_actions
3135!
3136!-- Count number of grid points with same facing and allocate attributes respectively
3137!-- Horizontal upward facing
3138    surf_h(0)%ns = ns_h_on_file(0)
3139    CALL allocate_surface_attributes_h( surf_h(0), nys, nyn, nxl, nxr )
3140!
3141!-- Horizontal downward facing
3142    surf_h(1)%ns = ns_h_on_file(1)
3143    CALL allocate_surface_attributes_h( surf_h(1), nys, nyn, nxl, nxr )
3144!
3145!-- Model top
3146    surf_h(2)%ns = ns_h_on_file(2)
3147    CALL allocate_surface_attributes_h_top( surf_h(2), nys, nyn, nxl, nxr )
3148!
3149!-- Vertical surfaces
3150    DO  l = 0, 3
3151       surf_v(l)%ns = ns_v_on_file(l)
3152       CALL allocate_surface_attributes_v( surf_v(l), nys, nyn, nxl, nxr )
3153    ENDDO
3154!
3155!-- In the following, gather data from surfaces elements with the same facing (but possibly differt
3156!-- type) on 1 data-type array.
3157    mm(0:2) = 1
3158    DO  l = 0, 2
3159       DO  i = nxl, nxr
3160          DO  j = nys, nyn
3161             DO  m = surf_def_h(l)%start_index(j,i), surf_def_h(l)%end_index(j,i)
3162                IF ( ALLOCATED( surf_def_h(l)%us ) )  surf_h(l)%us(mm(l)) = surf_def_h(l)%us(m)
3163                IF ( ALLOCATED( surf_def_h(l)%ts ) )  surf_h(l)%ts(mm(l)) = surf_def_h(l)%ts(m)
3164                IF ( ALLOCATED( surf_def_h(l)%qs ) )  surf_h(l)%qs(mm(l)) = surf_def_h(l)%qs(m)
3165                IF ( ALLOCATED( surf_def_h(l)%ss ) )  surf_h(l)%ss(mm(l)) = surf_def_h(l)%ss(m)
3166                IF ( ALLOCATED( surf_def_h(l)%qcs ) )  surf_h(l)%qcs(mm(l)) = surf_def_h(l)%qcs(m)
3167                IF ( ALLOCATED( surf_def_h(l)%ncs ) )  surf_h(l)%ncs(mm(l)) = surf_def_h(l)%ncs(m)
3168                IF ( ALLOCATED( surf_def_h(l)%qis ) )  surf_h(l)%qis(mm(l)) = surf_def_h(l)%qis(m)
3169                IF ( ALLOCATED( surf_def_h(l)%nis ) )  surf_h(l)%nis(mm(l)) = surf_def_h(l)%nis(m)
3170                IF ( ALLOCATED( surf_def_h(l)%qrs ) )  surf_h(l)%qrs(mm(l)) = surf_def_h(l)%qrs(m)
3171                IF ( ALLOCATED( surf_def_h(l)%nrs ) )  surf_h(l)%nrs(mm(l)) = surf_def_h(l)%nrs(m)
3172                IF ( ALLOCATED( surf_def_h(l)%ol ) )  surf_h(l)%ol(mm(l)) = surf_def_h(l)%ol(m)
3173                IF ( ALLOCATED( surf_def_h(l)%rib ) )  surf_h(l)%rib(mm(l)) = surf_def_h(l)%rib(m)
3174                IF ( ALLOCATED( surf_def_h(l)%pt_surface ) )                                       &
3175                   surf_h(l)%pt_surface(mm(l)) = surf_def_h(l)%pt_surface(m)
3176                IF ( ALLOCATED( surf_def_h(l)%q_surface ) )                                        &
3177                   surf_h(l)%q_surface(mm(l)) = surf_def_h(l)%q_surface(m)
3178                IF ( ALLOCATED( surf_def_h(l)%vpt_surface ) )                                      &
3179                   surf_h(l)%vpt_surface(mm(l)) = surf_def_h(l)%vpt_surface(m)
3180                IF ( ALLOCATED( surf_def_h(l)%usws ) )  surf_h(l)%usws(mm(l)) = surf_def_h(l)%usws(m)
3181                IF ( ALLOCATED( surf_def_h(l)%vsws ) )  surf_h(l)%vsws(mm(l)) = surf_def_h(l)%vsws(m)
3182                IF ( ALLOCATED( surf_def_h(l)%shf ) )  surf_h(l)%shf(mm(l)) = surf_def_h(l)%shf(m)
3183                IF ( ALLOCATED( surf_def_h(l)%qsws ) )  surf_h(l)%qsws(mm(l)) = surf_def_h(l)%qsws(m)
3184                IF ( ALLOCATED( surf_def_h(l)%ssws ) )  surf_h(l)%ssws(mm(l)) = surf_def_h(l)%ssws(m)
3185                IF ( ALLOCATED( surf_def_h(l)%css ) )  THEN
3186                   DO  lsp = 1,nvar
3187                      surf_h(l)%css(lsp,mm(l)) = surf_def_h(l)%css(lsp,m)
3188                   ENDDO
3189                ENDIF
3190                IF ( ALLOCATED( surf_def_h(l)%cssws ) )  THEN
3191                   DO  lsp = 1,nvar
3192                      surf_h(l)%cssws(lsp,mm(l)) = surf_def_h(l)%cssws(lsp,m)
3193                   ENDDO
3194                ENDIF
3195                IF ( ALLOCATED( surf_def_h(l)%qcsws ) )                                            &
3196                   surf_h(l)%qcsws(mm(l)) = surf_def_h(l)%qcsws(m)
3197                IF ( ALLOCATED( surf_def_h(l)%qrsws ) )                                            &
3198                   surf_h(l)%qrsws(mm(l)) = surf_def_h(l)%qrsws(m)
3199                IF ( ALLOCATED( surf_def_h(l)%qisws ) )                                            &
3200                   surf_h(l)%qisws(mm(l)) = surf_def_h(l)%qisws(m)
3201                IF ( ALLOCATED( surf_def_h(l)%ncsws ) )                                            &
3202                   surf_h(l)%ncsws(mm(l)) = surf_def_h(l)%ncsws(m)
3203                IF ( ALLOCATED( surf_def_h(l)%nisws ) )                                            &
3204                   surf_h(l)%nisws(mm(l)) = surf_def_h(l)%nisws(m)
3205                IF ( ALLOCATED( surf_def_h(l)%nrsws ) )                                            &
3206                   surf_h(l)%nrsws(mm(l)) = surf_def_h(l)%nrsws(m)
3207                IF ( ALLOCATED( surf_def_h(l)%sasws ) )                                            &
3208                   surf_h(l)%sasws(mm(l)) = surf_def_h(l)%sasws(m)
3209
3210                mm(l) = mm(l) + 1
3211             ENDDO
3212
3213             IF ( l < 2 )  THEN
3214                DO  m = surf_lsm_h(l)%start_index(j,i), surf_lsm_h(l)%end_index(j,i)
3215                   IF ( ALLOCATED( surf_lsm_h(l)%us ) )  surf_h(l)%us(mm(l)) = surf_lsm_h(l)%us(m)
3216                   IF ( ALLOCATED( surf_lsm_h(l)%ts ) )  surf_h(l)%ts(mm(l)) = surf_lsm_h(l)%ts(m)
3217                   IF ( ALLOCATED( surf_lsm_h(l)%qs ) )  surf_h(l)%qs(mm(l)) = surf_lsm_h(l)%qs(m)
3218                   IF ( ALLOCATED( surf_lsm_h(l)%ss ) )  surf_h(l)%ss(mm(l)) = surf_lsm_h(l)%ss(m)
3219                   IF ( ALLOCATED( surf_lsm_h(l)%qcs ) )  surf_h(l)%qcs(mm(l)) = surf_lsm_h(l)%qcs(m)
3220                   IF ( ALLOCATED( surf_lsm_h(l)%ncs ) )  surf_h(l)%ncs(mm(l)) = surf_lsm_h(l)%ncs(m)
3221                   IF ( ALLOCATED( surf_lsm_h(l)%qis ) )  surf_h(l)%qis(mm(l)) = surf_lsm_h(l)%qis(m)
3222                   IF ( ALLOCATED( surf_lsm_h(l)%nis ) )  surf_h(l)%nis(mm(l)) = surf_lsm_h(l)%nis(m)
3223                   IF ( ALLOCATED( surf_lsm_h(l)%qrs ) )  surf_h(l)%qrs(mm(l)) = surf_lsm_h(l)%qrs(m)
3224                   IF ( ALLOCATED( surf_lsm_h(l)%nrs ) )  surf_h(l)%nrs(mm(l)) = surf_lsm_h(l)%nrs(m)
3225                   IF ( ALLOCATED( surf_lsm_h(l)%ol ) )  surf_h(l)%ol(mm(l)) = surf_lsm_h(l)%ol(m)
3226                   IF ( ALLOCATED( surf_lsm_h(l)%rib ) )  surf_h(l)%rib(mm(l)) = surf_lsm_h(l)%rib(m)
3227                   IF ( ALLOCATED( surf_lsm_h(l)%pt_surface ) )                                       &
3228                      surf_h(l)%pt_surface(mm(l)) = surf_lsm_h(l)%pt_surface(m)
3229                   IF ( ALLOCATED( surf_def_h(l)%q_surface ) )                                        &
3230                      surf_h(l)%q_surface(mm(l)) = surf_lsm_h(l)%q_surface(m)
3231                   IF ( ALLOCATED( surf_def_h(l)%vpt_surface ) )                                      &
3232                      surf_h(l)%vpt_surface(mm(l)) = surf_lsm_h(l)%vpt_surface(m)
3233                   IF ( ALLOCATED( surf_lsm_h(l)%usws ) )  surf_h(l)%usws(mm(l)) = surf_lsm_h(l)%usws(m)
3234                   IF ( ALLOCATED( surf_lsm_h(l)%vsws ) )  surf_h(l)%vsws(mm(l)) = surf_lsm_h(l)%vsws(m)
3235                   IF ( ALLOCATED( surf_lsm_h(l)%shf ) )  surf_h(l)%shf(mm(l)) = surf_lsm_h(l)%shf(m)
3236                   IF ( ALLOCATED( surf_lsm_h(l)%qsws ) )  surf_h(l)%qsws(mm(l)) = surf_lsm_h(l)%qsws(m)
3237                   IF ( ALLOCATED( surf_lsm_h(l)%ssws ) )  surf_h(l)%ssws(mm(l)) = surf_lsm_h(l)%ssws(m)
3238                   IF ( ALLOCATED( surf_lsm_h(l)%css ) )  THEN
3239                      DO  lsp = 1, nvar
3240                         surf_h(l)%css(lsp,mm(l)) = surf_lsm_h(l)%css(lsp,m)
3241                      ENDDO
3242                   ENDIF
3243                   IF ( ALLOCATED( surf_lsm_h(l)%cssws ) )  THEN
3244                      DO  lsp = 1, nvar
3245                         surf_h(l)%cssws(lsp,mm(l)) = surf_lsm_h(l)%cssws(lsp,m)
3246                      ENDDO
3247                   ENDIF
3248                   IF ( ALLOCATED( surf_lsm_h(l)%qcsws ) )                                            &
3249                      surf_h(l)%qcsws(mm(l)) = surf_lsm_h(l)%qcsws(m)
3250                   IF ( ALLOCATED( surf_lsm_h(l)%qisws ) )                                            &
3251                      surf_h(l)%qisws(mm(l)) = surf_lsm_h(l)%qisws(m)
3252                   IF ( ALLOCATED( surf_lsm_h(l)%qrsws ) )                                            &
3253                      surf_h(l)%qrsws(mm(l)) = surf_lsm_h(l)%qrsws(m)
3254                   IF ( ALLOCATED( surf_lsm_h(l)%ncsws ) )                                            &
3255                      surf_h(l)%ncsws(mm(l)) = surf_lsm_h(l)%ncsws(m)
3256                   IF ( ALLOCATED( surf_lsm_h(l)%nisws ) )                                            &
3257                      surf_h(l)%nisws(mm(l)) = surf_lsm_h(l)%nisws(m)
3258                   IF ( ALLOCATED( surf_lsm_h(l)%nrsws ) )                                            &
3259                      surf_h(l)%nrsws(mm(l)) = surf_lsm_h(l)%nrsws(m)
3260                   IF ( ALLOCATED( surf_lsm_h(l)%sasws ) )                                            &
3261                     surf_h(l)%sasws(mm(l)) = surf_lsm_h(l)%sasws(m)
3262
3263                   mm(l) = mm(l) + 1
3264
3265                ENDDO
3266
3267                DO  m = surf_usm_h(l)%start_index(j,i), surf_usm_h(l)%end_index(j,i)
3268                   IF ( ALLOCATED( surf_usm_h(l)%us ) )                                               &
3269                      surf_h(l)%us(mm(l)) = surf_usm_h(l)%us(m)
3270                   IF ( ALLOCATED( surf_usm_h(l)%ts ) )                                               &
3271                      surf_h(l)%ts(mm(l)) = surf_usm_h(l)%ts(m)
3272                   IF ( ALLOCATED( surf_usm_h(l)%qs ) )                                               &
3273                      surf_h(l)%qs(mm(l)) = surf_usm_h(l)%qs(m)
3274                   IF ( ALLOCATED( surf_usm_h(l)%ss ) )                                               &
3275                      surf_h(l)%ss(mm(l)) = surf_usm_h(l)%ss(m)
3276                   IF ( ALLOCATED( surf_usm_h(l)%qcs ) )                                              &
3277                      surf_h(l)%qcs(mm(l)) = surf_usm_h(l)%qcs(m)
3278                   IF ( ALLOCATED( surf_usm_h(l)%ncs ) )                                              &
3279                      surf_h(l)%ncs(mm(l)) = surf_usm_h(l)%ncs(m)
3280                   IF ( ALLOCATED( surf_usm_h(l)%qis ) )                                              &
3281                      surf_h(l)%qis(mm(l)) = surf_usm_h(l)%qis(m)
3282                   IF ( ALLOCATED( surf_usm_h(l)%nis ) )                                              &
3283                      surf_h(l)%nis(mm(l)) = surf_usm_h(l)%nis(m)
3284                   IF ( ALLOCATED( surf_usm_h(l)%qrs ) )                                              &
3285                      surf_h(l)%qrs(mm(l)) = surf_usm_h(l)%qrs(m)
3286                   IF ( ALLOCATED( surf_usm_h(l)%nrs ) )                                              &
3287                      surf_h(l)%nrs(mm(l)) = surf_usm_h(l)%nrs(m)
3288                   IF ( ALLOCATED( surf_usm_h(l)%ol ) )                                               &
3289                      surf_h(l)%ol(mm(l)) = surf_usm_h(l)%ol(m)
3290                   IF ( ALLOCATED( surf_usm_h(l)%rib ) )                                              &
3291                      surf_h(l)%rib(mm(l)) = surf_usm_h(l)%rib(m)
3292                   IF ( ALLOCATED( surf_usm_h(l)%pt_surface ) )                                       &
3293                      surf_h(l)%pt_surface(mm(l)) = surf_usm_h(l)%pt_surface(m)
3294                    IF ( ALLOCATED( surf_usm_h(l)%q_surface ) )                                       &
3295                      surf_h(l)%q_surface(mm(l)) = surf_usm_h(l)%q_surface(m)
3296                   IF ( ALLOCATED( surf_usm_h(l)%vpt_surface ) )                                      &
3297                      surf_h(l)%vpt_surface(mm(l)) = surf_usm_h(l)%vpt_surface(m)
3298                   IF ( ALLOCATED( surf_usm_h(l)%usws ) )                                             &
3299                      surf_h(l)%usws(mm(l)) = surf_usm_h(l)%usws(m)
3300                   IF ( ALLOCATED( surf_usm_h(l)%vsws ) )                                             &
3301                      surf_h(l)%vsws(mm(l)) = surf_usm_h(l)%vsws(m)
3302                   IF ( ALLOCATED( surf_usm_h(l)%shf ) )                                              &
3303                      surf_h(l)%shf(mm(l)) = surf_usm_h(l)%shf(m)
3304                   IF ( ALLOCATED( surf_usm_h(l)%qsws ) )                                             &
3305                      surf_h(l)%qsws(mm(l)) = surf_usm_h(l)%qsws(m)
3306                   IF ( ALLOCATED( surf_usm_h(l)%ssws ) )                                             &
3307                      surf_h(l)%ssws(mm(l)) = surf_usm_h(l)%ssws(m)
3308                   IF ( ALLOCATED( surf_usm_h(l)%css ) )  THEN
3309                      DO lsp = 1, nvar
3310                         surf_h(l)%css(lsp,mm(l)) = surf_usm_h(l)%css(lsp,m)
3311                      ENDDO
3312                   ENDIF
3313                   IF ( ALLOCATED( surf_usm_h(l)%cssws ) )  THEN
3314                      DO lsp = 1, nvar
3315                         surf_h(l)%cssws(lsp,mm(l)) = surf_usm_h(l)%cssws(lsp,m)
3316                      ENDDO
3317                   ENDIF
3318                   IF ( ALLOCATED( surf_usm_h(l)%qcsws ) )                                            &
3319                      surf_h(l)%qcsws(mm(l)) = surf_usm_h(l)%qcsws(m)
3320                   IF ( ALLOCATED( surf_usm_h(l)%qisws ) )                                            &
3321                      surf_h(l)%qisws(mm(l)) = surf_usm_h(l)%qisws(m)
3322                   IF ( ALLOCATED( surf_usm_h(l)%qrsws ) )                                            &
3323                      surf_h(l)%qrsws(mm(l)) = surf_usm_h(l)%qrsws(m)
3324                   IF ( ALLOCATED( surf_usm_h(l)%ncsws ) )                                            &
3325                      surf_h(l)%ncsws(mm(l))   = surf_usm_h(l)%ncsws(m)
3326                   IF ( ALLOCATED( surf_usm_h(l)%nrsws ) )                                            &
3327                      surf_h(l)%nrsws(mm(l)) = surf_usm_h(l)%nrsws(m)
3328                   IF ( ALLOCATED( surf_usm_h(l)%nisws ) )                                            &
3329                      surf_h(l)%nisws(mm(l)) = surf_usm_h(l)%nisws(m)
3330                   IF ( ALLOCATED( surf_usm_h(l)%sasws ) )                                            &
3331                     surf_h(l)%sasws(mm(l)) = surf_usm_h(l)%sasws(m)
3332
3333                   mm(l) = mm(l) + 1
3334
3335                ENDDO
3336
3337
3338             ENDIF
3339
3340          ENDDO
3341
3342       ENDDO
3343!
3344!--    Recalculate start- and end indices for gathered surface type.
3345       start_index_h(l) = 1
3346       DO  i = nxl, nxr
3347          DO  j = nys, nyn
3348
3349             surf_h(l)%start_index(j,i) = start_index_h(l)
3350             surf_h(l)%end_index(j,i) = surf_h(l)%start_index(j,i) - 1
3351
3352             DO  m = surf_def_h(l)%start_index(j,i), surf_def_h(l)%end_index(j,i)
3353                surf_h(l)%end_index(j,i) = surf_h(l)%end_index(j,i) + 1
3354             ENDDO
3355             IF ( l < 2 )  THEN
3356                DO  m = surf_lsm_h(l)%start_index(j,i), surf_lsm_h(l)%end_index(j,i)
3357                   surf_h(l)%end_index(j,i) = surf_h(l)%end_index(j,i) + 1
3358                ENDDO
3359                DO  m = surf_usm_h(l)%start_index(j,i), surf_usm_h(l)%end_index(j,i)
3360                   surf_h(l)%end_index(j,i) = surf_h(l)%end_index(j,i) + 1
3361                ENDDO
3362             ENDIF
3363
3364             start_index_h(l) = surf_h(l)%end_index(j,i) + 1
3365
3366          ENDDO
3367       ENDDO
3368    ENDDO
3369!
3370!-- Treat vertically orientated surface. Again, gather data from different surfaces types but
3371!-- identical orientation (e.g. northward-facing) onto one surface type which is output afterwards.
3372    mm(0:3) = 1
3373    DO  l = 0, 3
3374       DO  i = nxl, nxr
3375          DO  j = nys, nyn
3376             DO  m = surf_def_v(l)%start_index(j,i), surf_def_v(l)%end_index(j,i)
3377                IF ( ALLOCATED( surf_def_v(l)%us ) )                                               &
3378                   surf_v(l)%us(mm(l)) = surf_def_v(l)%us(m)
3379                IF ( ALLOCATED( surf_def_v(l)%ts ) )                                               &
3380                   surf_v(l)%ts(mm(l)) = surf_def_v(l)%ts(m)
3381                IF ( ALLOCATED( surf_def_v(l)%qs ) )                                               &
3382                   surf_v(l)%qs(mm(l)) = surf_def_v(l)%qs(m)
3383                IF ( ALLOCATED( surf_def_v(l)%ss ) )                                               &
3384                   surf_v(l)%ss(mm(l)) = surf_def_v(l)%ss(m)
3385                IF ( ALLOCATED( surf_def_v(l)%qcs ) )                                              &
3386                   surf_v(l)%qcs(mm(l)) = surf_def_v(l)%qcs(m)
3387                IF ( ALLOCATED( surf_def_v(l)%ncs ) )                                              &
3388                   surf_v(l)%ncs(mm(l)) = surf_def_v(l)%ncs(m)
3389                IF ( ALLOCATED( surf_def_v(l)%qis ) )                                              &
3390                   surf_v(l)%qis(mm(l)) = surf_def_v(l)%qis(m)
3391                IF ( ALLOCATED( surf_def_v(l)%nis ) )                                              &
3392                   surf_v(l)%nis(mm(l)) = surf_def_v(l)%nis(m)
3393                IF ( ALLOCATED( surf_def_v(l)%qrs ) )                                              &
3394                   surf_v(l)%qrs(mm(l)) = surf_def_v(l)%qrs(m)
3395                IF ( ALLOCATED( surf_def_v(l)%nrs ) )                                              &
3396                   surf_v(l)%nrs(mm(l)) = surf_def_v(l)%nrs(m)
3397                IF ( ALLOCATED( surf_def_v(l)%ol ) )                                               &
3398                   surf_v(l)%ol(mm(l)) = surf_def_v(l)%ol(m)
3399                IF ( ALLOCATED( surf_def_v(l)%rib ) )                                              &
3400                   surf_v(l)%rib(mm(l)) = surf_def_v(l)%rib(m)
3401                IF ( ALLOCATED( surf_def_v(l)%pt_surface ) )                                       &
3402                   surf_v(l)%pt_surface(mm(l)) = surf_def_v(l)%pt_surface(m)
3403                IF ( ALLOCATED( surf_def_v(l)%q_surface ) )                                        &
3404                   surf_v(l)%q_surface(mm(l)) = surf_def_v(l)%q_surface(m)
3405                IF ( ALLOCATED( surf_def_v(l)%vpt_surface ) )                                      &
3406                   surf_v(l)%vpt_surface(mm(l)) = surf_def_v(l)%vpt_surface(m)
3407                IF ( ALLOCATED( surf_def_v(l)%shf ) )                                              &
3408                   surf_v(l)%shf(mm(l)) = surf_def_v(l)%shf(m)
3409                IF ( ALLOCATED( surf_def_v(l)%qsws ) )                                             &
3410                   surf_v(l)%qsws(mm(l)) = surf_def_v(l)%qsws(m)
3411                IF ( ALLOCATED( surf_def_v(l)%ssws ) )                                             &
3412                   surf_v(l)%ssws(mm(l)) = surf_def_v(l)%ssws(m)
3413                IF ( ALLOCATED( surf_def_v(l)%css ) )  THEN
3414                   DO  lsp = 1, nvar
3415                      surf_v(l)%css(lsp,mm(l)) = surf_def_v(l)%css(lsp,m)
3416                   ENDDO
3417                ENDIF
3418                IF ( ALLOCATED( surf_def_v(l)%cssws ) )  THEN
3419                   DO  lsp = 1, nvar
3420                      surf_v(l)%cssws(lsp,mm(l)) = surf_def_v(l)%cssws(lsp,m)
3421                   ENDDO
3422                ENDIF
3423                IF ( ALLOCATED( surf_def_v(l)%qcsws ) )                                            &
3424                   surf_v(l)%qcsws(mm(l)) = surf_def_v(l)%qcsws(m)
3425                IF ( ALLOCATED( surf_def_v(l)%qisws ) )                                            &
3426                   surf_v(l)%qisws(mm(l)) = surf_def_v(l)%qisws(m)
3427                IF ( ALLOCATED( surf_def_v(l)%qrsws ) )                                            &
3428                   surf_v(l)%qrsws(mm(l)) = surf_def_v(l)%qrsws(m)
3429                IF ( ALLOCATED( surf_def_v(l)%ncsws ) )                                            &
3430                   surf_v(l)%ncsws(mm(l)) = surf_def_v(l)%ncsws(m)
3431                IF ( ALLOCATED( surf_def_v(l)%nisws ) )                                            &
3432                   surf_v(l)%nisws(mm(l)) = surf_def_v(l)%nisws(m)
3433                IF ( ALLOCATED( surf_def_v(l)%nrsws ) )                                            &
3434                   surf_v(l)%nrsws(mm(l)) = surf_def_v(l)%nrsws(m)
3435                IF ( ALLOCATED( surf_def_v(l)%sasws ) )                                            &
3436                   surf_v(l)%sasws(mm(l)) = surf_def_v(l)%sasws(m)
3437                IF ( ALLOCATED( surf_def_v(l)%mom_flux_uv) )                                       &
3438                   surf_v(l)%mom_flux_uv(mm(l)) = surf_def_v(l)%mom_flux_uv(m)
3439                IF ( ALLOCATED( surf_def_v(l)%mom_flux_w) )                                        &
3440                   surf_v(l)%mom_flux_w(mm(l)) = surf_def_v(l)%mom_flux_w(m)
3441                IF ( ALLOCATED( surf_def_v(l)%mom_flux_tke) )                                      &
3442                   surf_v(l)%mom_flux_tke(0:1,mm(l)) = surf_def_v(l)%mom_flux_tke(0:1,m)
3443
3444                mm(l) = mm(l) + 1
3445             ENDDO
3446
3447             DO  m = surf_lsm_v(l)%start_index(j,i), surf_lsm_v(l)%end_index(j,i)
3448                IF ( ALLOCATED( surf_lsm_v(l)%us ) )                                               &
3449                   surf_v(l)%us(mm(l)) = surf_lsm_v(l)%us(m)
3450                IF ( ALLOCATED( surf_lsm_v(l)%ts ) )                                               &
3451                   surf_v(l)%ts(mm(l)) = surf_lsm_v(l)%ts(m)
3452                IF ( ALLOCATED( surf_lsm_v(l)%qs ) )                                               &
3453                   surf_v(l)%qs(mm(l)) = surf_lsm_v(l)%qs(m)
3454                IF ( ALLOCATED( surf_lsm_v(l)%ss ) )                                               &
3455                   surf_v(l)%ss(mm(l)) = surf_lsm_v(l)%ss(m)
3456                IF ( ALLOCATED( surf_lsm_v(l)%qcs ) )                                              &
3457                   surf_v(l)%qcs(mm(l)) = surf_lsm_v(l)%qcs(m)
3458                IF ( ALLOCATED( surf_lsm_v(l)%ncs ) )                                              &
3459                   surf_v(l)%ncs(mm(l)) = surf_lsm_v(l)%ncs(m)
3460                IF ( ALLOCATED( surf_lsm_v(l)%qis ) )                                              &
3461                   surf_v(l)%qis(mm(l)) = surf_lsm_v(l)%qis(m)
3462                IF ( ALLOCATED( surf_lsm_v(l)%nis ) )                                              &
3463                   surf_v(l)%nis(mm(l)) = surf_lsm_v(l)%nis(m)
3464                IF ( ALLOCATED( surf_lsm_v(l)%qrs ) )                                              &
3465                   surf_v(l)%qrs(mm(l)) = surf_lsm_v(l)%qrs(m)
3466                IF ( ALLOCATED( surf_lsm_v(l)%nrs ) )                                              &
3467                   surf_v(l)%nrs(mm(l)) = surf_lsm_v(l)%nrs(m)
3468                IF ( ALLOCATED( surf_lsm_v(l)%ol ) )                                               &
3469                   surf_v(l)%ol(mm(l)) = surf_lsm_v(l)%ol(m)
3470                IF ( ALLOCATED( surf_lsm_v(l)%rib ) )                                              &
3471                   surf_v(l)%rib(mm(l)) = surf_lsm_v(l)%rib(m)
3472                IF ( ALLOCATED( surf_lsm_v(l)%pt_surface ) )                                       &
3473                   surf_v(l)%pt_surface(mm(l)) = surf_lsm_v(l)%pt_surface(m)
3474                IF ( ALLOCATED( surf_lsm_v(l)%q_surface ) )                                        &
3475                   surf_v(l)%q_surface(mm(l)) = surf_lsm_v(l)%q_surface(m)
3476                IF ( ALLOCATED( surf_lsm_v(l)%vpt_surface ) )                                      &
3477                   surf_v(l)%vpt_surface(mm(l)) = surf_lsm_v(l)%vpt_surface(m)
3478                IF ( ALLOCATED( surf_lsm_v(l)%usws ) )                                             &
3479                   surf_v(l)%usws(mm(l)) = surf_lsm_v(l)%usws(m)
3480                IF ( ALLOCATED( surf_lsm_v(l)%vsws ) )                                             &
3481                   surf_v(l)%vsws(mm(l)) = surf_lsm_v(l)%vsws(m)
3482                IF ( ALLOCATED( surf_lsm_v(l)%shf ) )                                              &
3483                   surf_v(l)%shf(mm(l)) = surf_lsm_v(l)%shf(m)
3484                IF ( ALLOCATED( surf_lsm_v(l)%qsws ) )                                             &
3485                   surf_v(l)%qsws(mm(l)) = surf_lsm_v(l)%qsws(m)
3486                IF ( ALLOCATED( surf_lsm_v(l)%ssws ) )                                             &
3487                   surf_v(l)%ssws(mm(l)) = surf_lsm_v(l)%ssws(m)
3488                IF ( ALLOCATED( surf_lsm_v(l)%css ) )  THEN
3489                   DO  lsp = 1, nvar
3490                      surf_v(l)%css(lsp,mm(l)) = surf_lsm_v(l)%css(lsp,m)
3491                   ENDDO
3492                ENDIF
3493                IF ( ALLOCATED( surf_lsm_v(l)%cssws ) )  THEN
3494                   DO  lsp = 1, nvar
3495                      surf_v(l)%cssws(lsp,mm(l)) = surf_lsm_v(l)%cssws(lsp,m)
3496                   ENDDO
3497                ENDIF
3498                IF ( ALLOCATED( surf_lsm_v(l)%qcsws ) )                                            &
3499                   surf_v(l)%qcsws(mm(l)) = surf_lsm_v(l)%qcsws(m)
3500                IF ( ALLOCATED( surf_lsm_v(l)%qrsws ) )                                            &
3501                   surf_v(l)%qrsws(mm(l)) = surf_lsm_v(l)%qrsws(m)
3502                IF ( ALLOCATED( surf_lsm_v(l)%qisws ) )                                            &
3503                   surf_v(l)%qisws(mm(l)) = surf_lsm_v(l)%qisws(m)
3504                IF ( ALLOCATED( surf_lsm_v(l)%ncsws ) )                                            &
3505                   surf_v(l)%ncsws(mm(l)) = surf_lsm_v(l)%ncsws(m)
3506                IF ( ALLOCATED( surf_lsm_v(l)%nisws ) )                                            &
3507                   surf_v(l)%nisws(mm(l)) = surf_lsm_v(l)%nisws(m)
3508                IF ( ALLOCATED( surf_lsm_v(l)%nrsws ) )                                            &
3509                   surf_v(l)%nrsws(mm(l)) = surf_lsm_v(l)%nrsws(m)
3510                IF ( ALLOCATED( surf_lsm_v(l)%sasws ) )                                            &
3511                   surf_v(l)%sasws(mm(l)) = surf_lsm_v(l)%sasws(m)
3512                IF ( ALLOCATED( surf_lsm_v(l)%mom_flux_uv) )                                       &
3513                   surf_v(l)%mom_flux_uv(mm(l)) = surf_lsm_v(l)%mom_flux_uv(m)
3514                IF ( ALLOCATED( surf_lsm_v(l)%mom_flux_w) )                                        &
3515                   surf_v(l)%mom_flux_w(mm(l)) = surf_lsm_v(l)%mom_flux_w(m)
3516                IF ( ALLOCATED( surf_lsm_v(l)%mom_flux_tke) )                                      &
3517                   surf_v(l)%mom_flux_tke(0:1,mm(l)) = surf_lsm_v(l)%mom_flux_tke(0:1,m)
3518
3519                mm(l) = mm(l) + 1
3520             ENDDO
3521
3522             DO  m = surf_usm_v(l)%start_index(j,i), surf_usm_v(l)%end_index(j,i)
3523                IF ( ALLOCATED( surf_usm_v(l)%us ) )                                               &
3524                   surf_v(l)%us(mm(l)) = surf_usm_v(l)%us(m)
3525                IF ( ALLOCATED( surf_usm_v(l)%ts ) )                                               &
3526                   surf_v(l)%ts(mm(l)) = surf_usm_v(l)%ts(m)
3527                IF ( ALLOCATED( surf_usm_v(l)%qs ) )                                               &
3528                   surf_v(l)%qs(mm(l)) = surf_usm_v(l)%qs(m)
3529                IF ( ALLOCATED( surf_usm_v(l)%ss ) )                                               &
3530                   surf_v(l)%ss(mm(l)) = surf_usm_v(l)%ss(m)
3531                IF ( ALLOCATED( surf_usm_v(l)%qcs ) )                                              &
3532                   surf_v(l)%qcs(mm(l)) = surf_usm_v(l)%qcs(m)
3533                IF ( ALLOCATED( surf_usm_v(l)%ncs ) )                                              &
3534                   surf_v(l)%ncs(mm(l)) = surf_usm_v(l)%ncs(m)
3535                IF ( ALLOCATED( surf_usm_v(l)%qis ) )                                              &
3536                   surf_v(l)%qis(mm(l)) = surf_usm_v(l)%qis(m)
3537                IF ( ALLOCATED( surf_usm_v(l)%nis ) )                                              &
3538                   surf_v(l)%nis(mm(l)) = surf_usm_v(l)%nis(m)
3539                IF ( ALLOCATED( surf_usm_v(l)%qrs ) )                                              &
3540                   surf_v(l)%qrs(mm(l)) = surf_usm_v(l)%qrs(m)
3541                IF ( ALLOCATED( surf_usm_v(l)%nrs ) )                                              &
3542                   surf_v(l)%nrs(mm(l)) = surf_usm_v(l)%nrs(m)
3543                IF ( ALLOCATED( surf_usm_v(l)%ol ) )                                               &
3544                   surf_v(l)%ol(mm(l)) = surf_usm_v(l)%ol(m)
3545                IF ( ALLOCATED( surf_usm_v(l)%rib ) )                                              &
3546                   surf_v(l)%rib(mm(l)) = surf_usm_v(l)%rib(m)
3547                IF ( ALLOCATED( surf_usm_v(l)%pt_surface ) )                                       &
3548                   surf_v(l)%pt_surface(mm(l)) = surf_usm_v(l)%pt_surface(m)
3549                IF ( ALLOCATED( surf_usm_v(l)%q_surface ) )                                        &
3550                   surf_v(l)%q_surface(mm(l)) = surf_usm_v(l)%q_surface(m)
3551                IF ( ALLOCATED( surf_usm_v(l)%vpt_surface ) )                                      &
3552                   surf_v(l)%vpt_surface(mm(l)) = surf_usm_v(l)%vpt_surface(m)
3553                IF ( ALLOCATED( surf_usm_v(l)%usws ) )                                             &
3554                   surf_v(l)%usws(mm(l)) = surf_usm_v(l)%usws(m)
3555                IF ( ALLOCATED( surf_usm_v(l)%vsws ) )                                             &
3556                   surf_v(l)%vsws(mm(l)) = surf_usm_v(l)%vsws(m)
3557                IF ( ALLOCATED( surf_usm_v(l)%shf ) )                                              &
3558                   surf_v(l)%shf(mm(l)) = surf_usm_v(l)%shf(m)
3559                IF ( ALLOCATED( surf_usm_v(l)%qsws ) )                                             &
3560                   surf_v(l)%qsws(mm(l)) = surf_usm_v(l)%qsws(m)
3561                IF ( ALLOCATED( surf_usm_v(l)%ssws ) )                                             &
3562                   surf_v(l)%ssws(mm(l)) = surf_usm_v(l)%ssws(m)
3563                IF ( ALLOCATED( surf_usm_v(l)%css ) )  THEN
3564                   DO  lsp = 1, nvar
3565                      surf_v(l)%css(lsp,mm(l)) = surf_usm_v(l)%css(lsp,m)
3566                   ENDDO
3567                ENDIF
3568                IF ( ALLOCATED( surf_usm_v(l)%cssws ) )  THEN
3569                   DO  lsp = 1, nvar
3570                      surf_v(l)%cssws(lsp,mm(l)) = surf_usm_v(l)%cssws(lsp,m)
3571                   ENDDO
3572                ENDIF
3573                IF ( ALLOCATED( surf_usm_v(l)%qcsws ) )                                            &
3574                   surf_v(l)%qcsws(mm(l)) = surf_usm_v(l)%qcsws(m)
3575                IF ( ALLOCATED( surf_usm_v(l)%qrsws ) )                                            &
3576                   surf_v(l)%qrsws(mm(l)) = surf_usm_v(l)%qrsws(m)
3577                IF ( ALLOCATED( surf_usm_v(l)%qisws ) )                                            &
3578                   surf_v(l)%qisws(mm(l)) = surf_usm_v(l)%qisws(m)
3579                IF ( ALLOCATED( surf_usm_v(l)%ncsws ) )                                            &
3580                   surf_v(l)%ncsws(mm(l)) = surf_usm_v(l)%ncsws(m)
3581                IF ( ALLOCATED( surf_usm_v(l)%nisws ) )                                            &
3582                   surf_v(l)%nisws(mm(l)) = surf_usm_v(l)%nisws(m)
3583                IF ( ALLOCATED( surf_usm_v(l)%nrsws ) )                                            &
3584                   surf_v(l)%nrsws(mm(l)) = surf_usm_v(l)%nrsws(m)
3585                IF ( ALLOCATED( surf_usm_v(l)%sasws ) )                                            &
3586                   surf_v(l)%sasws(mm(l)) = surf_usm_v(l)%sasws(m)
3587                IF ( ALLOCATED( surf_usm_v(l)%mom_flux_uv) )                                       &
3588                   surf_v(l)%mom_flux_uv(mm(l)) = surf_usm_v(l)%mom_flux_uv(m)
3589                IF ( ALLOCATED( surf_usm_v(l)%mom_flux_w) )                                        &
3590                   surf_v(l)%mom_flux_w(mm(l)) = surf_usm_v(l)%mom_flux_w(m)
3591                IF ( ALLOCATED( surf_usm_v(l)%mom_flux_tke) )                                      &
3592                   surf_v(l)%mom_flux_tke(0:1,mm(l)) = surf_usm_v(l)%mom_flux_tke(0:1,m)
3593
3594                mm(l) = mm(l) + 1
3595             ENDDO
3596
3597          ENDDO
3598       ENDDO
3599!
3600!--    Recalculate start- and end-indices for gathered surface type
3601       start_index_v(l) = 1
3602       DO  i = nxl, nxr
3603          DO  j = nys, nyn
3604
3605             surf_v(l)%start_index(j,i) = start_index_v(l)
3606             surf_v(l)%end_index(j,i)   = surf_v(l)%start_index(j,i) -1
3607
3608             DO  m = surf_def_v(l)%start_index(j,i), surf_def_v(l)%end_index(j,i)
3609                surf_v(l)%end_index(j,i) = surf_v(l)%end_index(j,i) + 1
3610             ENDDO
3611             DO  m = surf_lsm_v(l)%start_index(j,i), surf_lsm_v(l)%end_index(j,i)
3612                surf_v(l)%end_index(j,i) = surf_v(l)%end_index(j,i) + 1
3613             ENDDO
3614             DO  m = surf_usm_v(l)%start_index(j,i), surf_usm_v(l)%end_index(j,i)
3615                surf_v(l)%end_index(j,i) = surf_v(l)%end_index(j,i) + 1
3616             ENDDO
3617
3618             start_index_v(l) = surf_v(l)%end_index(j,i) + 1
3619          ENDDO
3620       ENDDO
3621
3622    ENDDO
3623
3624!
3625!-- Now start writing restart data to file
3626    IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
3627
3628!
3629!--    Output strings for the total number of upward / downward-facing surfaces on subdomain.
3630       CALL wrd_write_string( 'ns_h_on_file' )
3631       WRITE ( 14 ) ns_h_on_file
3632!
3633!--    Output strings for the total number of north/south/east/westward-facing surfaces on subdomain.
3634       CALL wrd_write_string( 'ns_v_on_file' )
3635       WRITE ( 14 ) ns_v_on_file
3636
3637!
3638!--    Horizontal surfaces (upward-, downward-facing, and model top).
3639!--    Always start with %start_index followed by %end_index
3640       DO  l = 0, 2
3641          WRITE( dum, '(I1)') l
3642
3643          CALL wrd_write_string( 'surf_h(' // dum // ')%start_index' )
3644          WRITE ( 14 ) surf_h(l)%start_index
3645
3646          CALL wrd_write_string( 'surf_h(' // dum // ')%end_index' )
3647          WRITE ( 14 ) surf_h(l)%end_index
3648
3649          IF ( ALLOCATED ( surf_h(l)%us ) )  THEN
3650             CALL wrd_write_string( 'surf_h(' // dum // ')%us' )
3651             WRITE ( 14 ) surf_h(l)%us
3652          ENDIF
3653
3654          IF ( ALLOCATED ( surf_h(l)%ts ) )  THEN
3655             CALL wrd_write_string( 'surf_h(' // dum // ')%ts' )
3656             WRITE ( 14 ) surf_h(l)%ts
3657          ENDIF
3658
3659          IF ( ALLOCATED ( surf_h(l)%qs ) )  THEN
3660             CALL wrd_write_string( 'surf_h(' // dum // ')%qs' )
3661             WRITE ( 14 ) surf_h(l)%qs
3662          ENDIF
3663
3664          IF ( ALLOCATED ( surf_h(l)%ss ) )  THEN
3665             CALL wrd_write_string( 'surf_h(' // dum // ')%ss' )
3666             WRITE ( 14 ) surf_h(l)%ss
3667          ENDIF
3668
3669          IF ( ALLOCATED ( surf_h(l)%qcs ) )  THEN
3670             CALL wrd_write_string( 'surf_h(' // dum // ')%qcs' )
3671             WRITE ( 14 ) surf_h(l)%qcs
3672          ENDIF
3673
3674          IF ( ALLOCATED ( surf_h(l)%ncs ) )  THEN
3675             CALL wrd_write_string( 'surf_h(' // dum // ')%ncs' )
3676             WRITE ( 14 ) surf_h(l)%ncs
3677          ENDIF
3678
3679          IF ( ALLOCATED ( surf_h(l)%qis ) )  THEN
3680             CALL wrd_write_string( 'surf_h(' // dum // ')%qis' )
3681             WRITE ( 14 ) surf_h(l)%qis
3682          ENDIF
3683
3684          IF ( ALLOCATED ( surf_h(l)%nis ) )  THEN
3685             CALL wrd_write_string( 'surf_h(' // dum // ')%nis' )
3686             WRITE ( 14 ) surf_h(l)%nis
3687          ENDIF
3688
3689          IF ( ALLOCATED ( surf_h(l)%qrs ) )  THEN
3690             CALL wrd_write_string( 'surf_h(' // dum // ')%qrs' )
3691             WRITE ( 14 ) surf_h(l)%qrs
3692          ENDIF
3693
3694          IF ( ALLOCATED ( surf_h(l)%nrs ) )  THEN
3695             CALL wrd_write_string( 'surf_h(' // dum // ')%nrs' )
3696             WRITE ( 14 ) surf_h(l)%nrs
3697          ENDIF
3698
3699          IF ( ALLOCATED ( surf_h(l)%ol ) )  THEN
3700             CALL wrd_write_string( 'surf_h(' // dum // ')%ol' )
3701             WRITE ( 14 ) surf_h(l)%ol
3702          ENDIF
3703
3704          IF ( ALLOCATED ( surf_h(l)%rib ) )  THEN
3705             CALL wrd_write_string( 'surf_h(' // dum // ')%rib' )
3706             WRITE ( 14 ) surf_h(l)%rib
3707          ENDIF
3708
3709          IF ( ALLOCATED ( surf_h(l)%pt_surface ) )  THEN
3710             CALL wrd_write_string( 'surf_h(' // dum // ')%pt_surface' )
3711             WRITE ( 14 ) surf_h(l)%pt_surface
3712          ENDIF
3713
3714          IF ( ALLOCATED ( surf_h(l)%q_surface ) )  THEN
3715             CALL wrd_write_string( 'surf_h(' // dum // ')%q_surface' )
3716             WRITE ( 14 ) surf_h(l)%q_surface
3717          ENDIF
3718
3719          IF ( ALLOCATED ( surf_h(l)%vpt_surface ) )  THEN
3720             CALL wrd_write_string( 'surf_h(' // dum // ')%vpt_surface' )
3721             WRITE ( 14 ) surf_h(l)%vpt_surface
3722          ENDIF
3723
3724          IF ( ALLOCATED ( surf_h(l)%usws ) )  THEN
3725             CALL wrd_write_string( 'surf_h(' // dum // ')%usws' )
3726             WRITE ( 14 ) surf_h(l)%usws
3727          ENDIF
3728
3729          IF ( ALLOCATED ( surf_h(l)%vsws ) )  THEN
3730             CALL wrd_write_string( 'surf_h(' // dum // ')%vsws' )
3731             WRITE ( 14 ) surf_h(l)%vsws
3732          ENDIF
3733
3734          IF ( ALLOCATED ( surf_h(l)%shf ) )  THEN
3735             CALL wrd_write_string( 'surf_h(' // dum // ')%shf' )
3736             WRITE ( 14 ) surf_h(l)%shf
3737          ENDIF
3738
3739          IF ( ALLOCATED ( surf_h(l)%qsws ) )  THEN
3740             CALL wrd_write_string( 'surf_h(' // dum // ')%qsws' )
3741             WRITE ( 14 ) surf_h(l)%qsws
3742          ENDIF
3743
3744          IF ( ALLOCATED ( surf_h(l)%ssws ) )  THEN
3745             CALL wrd_write_string( 'surf_h(' // dum // ')%ssws' )
3746             WRITE ( 14 ) surf_h(l)%ssws
3747          ENDIF
3748
3749          IF ( ALLOCATED ( surf_h(l)%css ) )  THEN
3750             CALL wrd_write_string( 'surf_h(' // dum // ')%css' )
3751             WRITE ( 14 ) surf_h(l)%css
3752          ENDIF
3753
3754          IF ( ALLOCATED ( surf_h(l)%cssws ) )  THEN
3755             CALL wrd_write_string( 'surf_h(' // dum // ')%cssws' )
3756             WRITE ( 14 )  surf_h(l)%cssws
3757          ENDIF
3758
3759          IF ( ALLOCATED ( surf_h(l)%qcsws ) )  THEN
3760             CALL wrd_write_string( 'surf_h(' // dum // ')%qcsws' )
3761             WRITE ( 14 ) surf_h(l)%qcsws
3762          ENDIF
3763
3764          IF ( ALLOCATED ( surf_h(l)%ncsws ) )  THEN
3765             CALL wrd_write_string( 'surf_h(' // dum // ')%ncsws' )
3766             WRITE ( 14 ) surf_h(l)%ncsws
3767          ENDIF
3768
3769          IF ( ALLOCATED ( surf_h(l)%qisws ) )  THEN
3770             CALL wrd_write_string( 'surf_h(' // dum // ')%qisws' )
3771             WRITE ( 14 ) surf_h(l)%qisws
3772          ENDIF
3773
3774          IF ( ALLOCATED ( surf_h(l)%nisws ) )  THEN
3775             CALL wrd_write_string( 'surf_h(' // dum // ')%nisws' )
3776             WRITE ( 14 ) surf_h(l)%nisws
3777          ENDIF
3778
3779          IF ( ALLOCATED ( surf_h(l)%qrsws ) )  THEN
3780             CALL wrd_write_string( 'surf_h(' // dum // ')%qrsws' )
3781             WRITE ( 14 ) surf_h(l)%qrsws
3782          ENDIF
3783
3784          IF ( ALLOCATED ( surf_h(l)%nrsws ) )  THEN
3785             CALL wrd_write_string( 'surf_h(' // dum // ')%nrsws' )
3786             WRITE ( 14 ) surf_h(l)%nrsws
3787          ENDIF
3788
3789          IF ( ALLOCATED ( surf_h(l)%sasws ) )  THEN
3790             CALL wrd_write_string( 'surf_h(' // dum // ')%sasws' )
3791             WRITE ( 14 ) surf_h(l)%sasws
3792          ENDIF
3793
3794       ENDDO
3795!
3796!--    Write vertical surfaces.
3797!--    Always start with %start_index followed by %end_index.
3798       DO  l = 0, 3
3799          WRITE( dum, '(I1)') l
3800
3801          CALL wrd_write_string( 'surf_v(' // dum // ')%start_index' )
3802          WRITE ( 14 ) surf_v(l)%start_index
3803
3804          CALL wrd_write_string( 'surf_v(' // dum // ')%end_index' )
3805          WRITE ( 14 ) surf_v(l)%end_index
3806
3807          IF ( ALLOCATED ( surf_v(l)%us ) )  THEN
3808             CALL wrd_write_string( 'surf_v(' // dum // ')%us' )
3809             WRITE ( 14 ) surf_v(l)%us
3810          ENDIF
3811
3812          IF ( ALLOCATED ( surf_v(l)%ts ) )  THEN
3813             CALL wrd_write_string( 'surf_v(' // dum // ')%ts' )
3814             WRITE ( 14 ) surf_v(l)%ts
3815          ENDIF
3816
3817          IF ( ALLOCATED ( surf_v(l)%qs ) )  THEN
3818             CALL wrd_write_string( 'surf_v(' // dum // ')%qs' )
3819             WRITE ( 14 ) surf_v(l)%qs
3820          ENDIF
3821
3822          IF ( ALLOCATED ( surf_v(l)%ss ) )  THEN
3823             CALL wrd_write_string( 'surf_v(' // dum // ')%ss' )
3824             WRITE ( 14 ) surf_v(l)%ss
3825          ENDIF
3826
3827          IF ( ALLOCATED ( surf_v(l)%qcs ) )  THEN
3828             CALL wrd_write_string( 'surf_v(' // dum // ')%qcs' )
3829             WRITE ( 14 ) surf_v(l)%qcs
3830          ENDIF
3831
3832          IF ( ALLOCATED ( surf_v(l)%ncs ) )  THEN
3833             CALL wrd_write_string( 'surf_v(' // dum // ')%ncs' )
3834             WRITE ( 14 ) surf_v(l)%ncs
3835          ENDIF
3836
3837          IF ( ALLOCATED ( surf_v(l)%qis ) )  THEN
3838             CALL wrd_write_string( 'surf_v(' // dum // ')%qis' )
3839             WRITE ( 14 ) surf_v(l)%qis
3840          ENDIF
3841
3842          IF ( ALLOCATED ( surf_v(l)%nis ) )  THEN
3843             CALL wrd_write_string( 'surf_v(' // dum // ')%nis' )
3844             WRITE ( 14 ) surf_v(l)%nis
3845          ENDIF
3846
3847          IF ( ALLOCATED ( surf_v(l)%qrs ) )  THEN
3848             CALL wrd_write_string( 'surf_v(' // dum // ')%qrs' )
3849             WRITE ( 14 ) surf_v(l)%qrs
3850          ENDIF
3851
3852          IF ( ALLOCATED ( surf_v(l)%nrs ) )  THEN
3853             CALL wrd_write_string( 'surf_v(' // dum // ')%nrs' )
3854             WRITE ( 14 ) surf_v(l)%nrs
3855          ENDIF
3856
3857          IF ( ALLOCATED ( surf_v(l)%ol ) )  THEN
3858             CALL wrd_write_string( 'surf_v(' // dum // ')%ol' )
3859             WRITE ( 14 ) surf_v(l)%ol
3860          ENDIF
3861
3862          IF ( ALLOCATED ( surf_v(l)%rib ) )  THEN
3863             CALL wrd_write_string( 'surf_v(' // dum // ')%rib' )
3864             WRITE ( 14 ) surf_v(l)%rib
3865          ENDIF
3866
3867          IF ( ALLOCATED ( surf_v(l)%pt_surface ) )  THEN
3868             CALL wrd_write_string( 'surf_v(' // dum // ')%pt_surface' )
3869             WRITE ( 14 ) surf_v(l)%pt_surface
3870          ENDIF
3871
3872          IF ( ALLOCATED ( surf_v(l)%q_surface ) )  THEN
3873             CALL wrd_write_string( 'surf_v(' // dum // ')%q_surface' )
3874             WRITE ( 14 ) surf_v(l)%q_surface
3875          ENDIF
3876
3877          IF ( ALLOCATED ( surf_v(l)%vpt_surface ) )  THEN
3878             CALL wrd_write_string( 'surf_v(' // dum // ')%vpt_surface' )
3879             WRITE ( 14 ) surf_v(l)%vpt_surface
3880          ENDIF
3881
3882          IF ( ALLOCATED ( surf_v(l)%shf ) )  THEN
3883             CALL wrd_write_string( 'surf_v(' // dum // ')%shf' )
3884             WRITE ( 14 ) surf_v(l)%shf
3885          ENDIF
3886
3887          IF ( ALLOCATED ( surf_v(l)%qsws ) )  THEN
3888             CALL wrd_write_string( 'surf_v(' // dum // ')%qsws' )
3889             WRITE ( 14 ) surf_v(l)%qsws
3890          ENDIF
3891
3892          IF ( ALLOCATED ( surf_v(l)%ssws ) )  THEN
3893             CALL wrd_write_string( 'surf_v(' // dum // ')%ssws' )
3894             WRITE ( 14 ) surf_v(l)%ssws
3895          ENDIF
3896
3897          IF ( ALLOCATED ( surf_v(l)%css ) )  THEN
3898             CALL wrd_write_string( 'surf_v(' // dum // ')%css' )
3899             WRITE ( 14 ) surf_v(l)%css
3900          ENDIF
3901
3902          IF ( ALLOCATED ( surf_v(l)%cssws ) )  THEN
3903             CALL wrd_write_string( 'surf_v(' // dum // ')%cssws' )
3904             WRITE ( 14 ) surf_v(l)%cssws
3905          ENDIF
3906
3907          IF ( ALLOCATED ( surf_v(l)%qcsws ) )  THEN
3908             CALL wrd_write_string( 'surf_v(' // dum // ')%qcsws' )
3909             WRITE ( 14 ) surf_v(l)%qcsws
3910          ENDIF
3911
3912          IF ( ALLOCATED ( surf_v(l)%ncsws ) )  THEN
3913             CALL wrd_write_string( 'surf_v(' // dum // ')%ncsws' )
3914             WRITE ( 14 ) surf_v(l)%ncsws
3915          ENDIF
3916
3917          IF ( ALLOCATED ( surf_v(l)%qisws ) )  THEN
3918             CALL wrd_write_string( 'surf_v(' // dum // ')%qisws' )
3919             WRITE ( 14 ) surf_v(l)%qisws
3920          ENDIF
3921
3922          IF ( ALLOCATED ( surf_v(l)%nisws ) )  THEN
3923             CALL wrd_write_string( 'surf_v(' // dum // ')%nisws' )
3924             WRITE ( 14 ) surf_v(l)%nisws
3925          ENDIF
3926
3927          IF ( ALLOCATED ( surf_v(l)%qrsws ) )  THEN
3928             CALL wrd_write_string( 'surf_v(' // dum // ')%qrsws' )
3929             WRITE ( 14 ) surf_v(l)%qrsws
3930          ENDIF
3931
3932          IF ( ALLOCATED ( surf_v(l)%nrsws ) )  THEN
3933             CALL wrd_write_string( 'surf_v(' // dum // ')%nrsws' )
3934             WRITE ( 14 ) surf_v(l)%nrsws
3935          ENDIF
3936
3937          IF ( ALLOCATED ( surf_v(l)%sasws ) )  THEN
3938             CALL wrd_write_string( 'surf_v(' // dum // ')%sasws' )
3939             WRITE ( 14 ) surf_v(l)%sasws
3940          ENDIF
3941
3942          IF ( ALLOCATED ( surf_v(l)%mom_flux_uv ) )  THEN
3943             CALL wrd_write_string( 'surf_v(' // dum // ')%mom_uv' )
3944             WRITE ( 14 ) surf_v(l)%mom_flux_uv
3945          ENDIF
3946
3947          IF ( ALLOCATED ( surf_v(l)%mom_flux_w ) )  THEN
3948             CALL wrd_write_string( 'surf_v(' // dum // ')%mom_w' )
3949             WRITE ( 14 ) surf_v(l)%mom_flux_w
3950          ENDIF
3951
3952          IF ( ALLOCATED ( surf_v(l)%mom_flux_tke ) )  THEN
3953             CALL wrd_write_string( 'surf_v(' // dum // ')%mom_tke' )
3954             WRITE ( 14 ) surf_v(l)%mom_flux_tke
3955          ENDIF
3956
3957       ENDDO
3958
3959    ELSEIF ( restart_data_format_output(1:3) == 'mpi' )  THEN
3960
3961!
3962!--    Start with horizontal surfaces (upward-, downward-facing, and model top).
3963!--    All data writen with rd_mpi_io_write_surface are globally indexed 1d-arrays.
3964       ns_h_on_file = 0
3965       ns_v_on_file = 0
3966
3967       DO  l = 0, 2
3968
3969          WRITE( dum, '(I1)') l
3970
3971          CALL rd_mpi_io_surface_filetypes( surf_h(l)%start_index, surf_h(l)%end_index,            &
3972                                            surface_data_to_write, global_start_index )
3973          IF ( .NOT. surface_data_to_write )  CYCLE
3974
3975          ns_h_on_file(l) = total_number_of_surface_values
3976
3977          CALL wrd_mpi_io( 'surf_h(' // dum // ')%start_index', surf_h(l)%start_index )
3978          CALL wrd_mpi_io( 'surf_h(' // dum // ')%end_index', surf_h(l)%end_index )
3979          CALL wrd_mpi_io( 'global_start_index_h_' // dum, global_start_index )
3980
3981          IF ( ALLOCATED ( surf_h(l)%us ) )  THEN
3982             CALL wrd_mpi_io_surface ( 'surf_h(' // dum // ')%us', surf_h(l)%us )
3983          ENDIF
3984
3985          IF ( ALLOCATED ( surf_h(l)%ts ) )  THEN
3986             CALL wrd_mpi_io_surface ( 'surf_h(' // dum // ')%ts', surf_h(l)%ts )
3987          ENDIF
3988
3989          IF ( ALLOCATED ( surf_h(l)%qs ) )  THEN
3990             CALL wrd_mpi_io_surface ( 'surf_h(' // dum // ')%qs', surf_h(l)%qs )
3991          ENDIF
3992
3993          IF ( ALLOCATED ( surf_h(l)%ss ) )  THEN
3994             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%ss', surf_h(l)%ss )
3995          ENDIF
3996
3997          IF ( ALLOCATED ( surf_h(l)%qcs ) )  THEN
3998             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%qcs', surf_h(l)%qcs )
3999          ENDIF
4000
4001          IF ( ALLOCATED ( surf_h(l)%ncs ) )  THEN
4002             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%ncs', surf_h(l)%ncs )
4003          ENDIF
4004
4005          IF ( ALLOCATED ( surf_h(l)%qis ) )  THEN
4006             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%qis', surf_h(l)%qis )
4007          ENDIF
4008
4009          IF ( ALLOCATED ( surf_h(l)%nis ) )  THEN
4010             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%nis', surf_h(l)%nis )
4011          ENDIF
4012
4013          IF ( ALLOCATED ( surf_h(l)%qrs ) )  THEN
4014             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%qrs', surf_h(l)%qrs )
4015          ENDIF
4016
4017          IF ( ALLOCATED ( surf_h(l)%nrs ) )  THEN
4018             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%nrs', surf_h(l)%nrs )
4019          ENDIF
4020
4021          IF ( ALLOCATED ( surf_h(l)%ol ) )  THEN
4022             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%ol', surf_h(l)%ol )
4023          ENDIF
4024
4025          IF ( ALLOCATED ( surf_h(l)%rib ) )  THEN
4026            CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%rib', surf_h(l)%rib )
4027          ENDIF
4028
4029          IF ( ALLOCATED ( surf_h(l)%pt_surface ) )  THEN
4030             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%pt_surface', surf_h(l)%pt_surface )
4031          ENDIF
4032
4033          IF ( ALLOCATED ( surf_h(l)%q_surface ) )  THEN
4034             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%q_surface', surf_h(l)%q_surface )
4035          ENDIF
4036
4037          IF ( ALLOCATED ( surf_h(l)%vpt_surface ) )  THEN
4038             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%vpt_surface', surf_h(l)%vpt_surface )
4039          ENDIF
4040
4041          IF ( ALLOCATED ( surf_h(l)%usws ) )  THEN
4042             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%usws', surf_h(l)%usws )
4043          ENDIF
4044
4045          IF ( ALLOCATED ( surf_h(l)%vsws ) )  THEN
4046             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%vsws', surf_h(l)%vsws )
4047          ENDIF
4048
4049          IF ( ALLOCATED ( surf_h(l)%shf ) )  THEN
4050             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%shf', surf_h(l)%shf )
4051          ENDIF
4052
4053          IF ( ALLOCATED ( surf_h(l)%qsws ) )  THEN
4054             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%qsws', surf_h(l)%qsws )
4055          ENDIF
4056
4057          IF ( ALLOCATED ( surf_h(l)%ssws ) )  THEN
4058             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%ssws', surf_h(l)%ssws )
4059          ENDIF
4060
4061          IF ( ALLOCATED ( surf_h(l)%css ) )  THEN
4062             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%css', surf_h(l)%css )
4063          ENDIF
4064
4065          IF ( ALLOCATED ( surf_h(l)%cssws ) )  THEN
4066             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%cssws', surf_h(l)%cssws )
4067          ENDIF
4068
4069          IF ( ALLOCATED ( surf_h(l)%qcsws ) )  THEN
4070             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%qcsws', surf_h(l)%qcsws )
4071          ENDIF
4072
4073          IF ( ALLOCATED ( surf_h(l)%ncsws ) )  THEN
4074             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%ncsws', surf_h(l)%ncsws )
4075          ENDIF
4076
4077          IF ( ALLOCATED ( surf_h(l)%qisws ) )  THEN
4078             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%qisws', surf_h(l)%qisws )
4079          ENDIF
4080
4081          IF ( ALLOCATED ( surf_h(l)%nisws ) )  THEN
4082             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%nisws', surf_h(l)%nisws )
4083          ENDIF
4084
4085          IF ( ALLOCATED ( surf_h(l)%qrsws ) )  THEN
4086             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%qrsws', surf_h(l)%qrsws )
4087          ENDIF
4088
4089          IF ( ALLOCATED ( surf_h(l)%nrsws ) )  THEN
4090             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%nrsws', surf_h(l)%nrsws )
4091          ENDIF
4092
4093          IF ( ALLOCATED ( surf_h(l)%sasws ) )  THEN
4094             CALL wrd_mpi_io_surface( 'surf_h(' // dum // ')%sasws', surf_h(l)%sasws )
4095          ENDIF
4096
4097       ENDDO
4098!
4099!--    Write vertical surfaces
4100       DO  l = 0, 3
4101
4102          WRITE( dum, '(I1)') l
4103
4104          CALL rd_mpi_io_surface_filetypes( surf_v(l)%start_index, surf_v(l)%end_index,            &
4105                                            surface_data_to_write, global_start_index )
4106
4107          ns_v_on_file(l) = total_number_of_surface_values
4108
4109          CALL wrd_mpi_io( 'surf_v(' // dum // ')%start_index', surf_v(l)%start_index )
4110          CALL wrd_mpi_io( 'surf_v(' // dum // ')%end_index', surf_v(l)%end_index )
4111          CALL wrd_mpi_io( 'global_start_index_v_' // dum, global_start_index )
4112
4113          IF ( .NOT. surface_data_to_write )  CYCLE
4114
4115          IF ( ALLOCATED ( surf_v(l)%us ) )  THEN
4116             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%us',  surf_v(l)%us )
4117          ENDIF
4118
4119          IF ( ALLOCATED ( surf_v(l)%ts ) )  THEN
4120             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%ts', surf_v(l)%ts )
4121          ENDIF
4122
4123          IF ( ALLOCATED ( surf_v(l)%qs ) )  THEN
4124             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qs',  surf_v(l)%qs )
4125          ENDIF
4126
4127          IF ( ALLOCATED ( surf_v(l)%ss ) )  THEN
4128             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%ss',  surf_v(l)%ss )
4129          ENDIF
4130
4131          IF ( ALLOCATED ( surf_v(l)%qcs ) )  THEN
4132             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qcs', surf_v(l)%qcs )
4133          ENDIF
4134
4135          IF ( ALLOCATED ( surf_v(l)%ncs ) )  THEN
4136             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%ncs', surf_v(l)%ncs )
4137          ENDIF
4138
4139          IF ( ALLOCATED ( surf_v(l)%qis ) )  THEN
4140             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qis', surf_v(l)%qis )
4141          ENDIF
4142
4143          IF ( ALLOCATED ( surf_v(l)%nis ) )  THEN
4144             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%nis', surf_v(l)%nis )
4145          ENDIF
4146
4147          IF ( ALLOCATED ( surf_v(l)%qrs ) )  THEN
4148             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qrs', surf_v(l)%qrs )
4149          ENDIF
4150
4151          IF ( ALLOCATED ( surf_v(l)%nrs ) )  THEN
4152             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%nrs', surf_v(l)%nrs )
4153          ENDIF
4154
4155          IF ( ALLOCATED ( surf_v(l)%ol ) )  THEN
4156             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%ol', surf_v(l)%ol )
4157          ENDIF
4158
4159          IF ( ALLOCATED ( surf_v(l)%rib ) )  THEN
4160             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%rib', surf_v(l)%rib )
4161          ENDIF
4162
4163          IF ( ALLOCATED ( surf_v(l)%pt_surface ) )  THEN
4164             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%pt_surface', surf_v(l)%pt_surface )
4165          ENDIF
4166
4167          IF ( ALLOCATED ( surf_v(l)%q_surface ) )  THEN
4168             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%q_surface', surf_v(l)%q_surface )
4169          ENDIF
4170
4171          IF ( ALLOCATED ( surf_v(l)%vpt_surface ) )  THEN
4172             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%vpt_surface', surf_v(l)%vpt_surface )
4173          ENDIF
4174
4175          IF ( ALLOCATED ( surf_v(l)%shf ) )  THEN
4176             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%shf', surf_v(l)%shf )
4177          ENDIF
4178
4179          IF ( ALLOCATED ( surf_v(l)%qsws ) )  THEN
4180             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qsws', surf_v(l)%qsws )
4181           ENDIF
4182
4183          IF ( ALLOCATED ( surf_v(l)%ssws ) )  THEN
4184             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%ssws', surf_v(l)%ssws )
4185          ENDIF
4186
4187          IF ( ALLOCATED ( surf_v(l)%css ) )  THEN
4188             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%css', surf_v(l)%css )
4189          ENDIF
4190
4191          IF ( ALLOCATED ( surf_v(l)%cssws ) )  THEN
4192             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%cssws', surf_v(l)%cssws )
4193          ENDIF
4194
4195          IF ( ALLOCATED ( surf_v(l)%qcsws ) )  THEN
4196             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qcsws', surf_v(l)%qcsws )
4197          ENDIF
4198
4199          IF ( ALLOCATED ( surf_v(l)%ncsws ) )  THEN
4200             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%ncsws', surf_v(l)%ncsws )
4201          ENDIF
4202
4203          IF ( ALLOCATED ( surf_v(l)%qisws ) )  THEN
4204             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qisws', surf_v(l)%qisws )
4205          ENDIF
4206
4207          IF ( ALLOCATED ( surf_v(l)%nisws ) )  THEN
4208             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%nisws', surf_v(l)%nisws )
4209          ENDIF
4210
4211          IF ( ALLOCATED ( surf_v(l)%qrsws ) )  THEN
4212             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%qrsws', surf_v(l)%qrsws )
4213          ENDIF
4214
4215          IF ( ALLOCATED ( surf_v(l)%nrsws ) )  THEN
4216             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%nrsws', surf_v(l)%nrsws )
4217          ENDIF
4218
4219          IF ( ALLOCATED ( surf_v(l)%sasws ) )  THEN
4220             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%sasws', surf_v(l)%sasws )
4221          ENDIF
4222
4223          IF ( ALLOCATED ( surf_v(l)%mom_flux_uv ) )  THEN
4224             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%mom_uv', surf_v(l)%mom_flux_uv )
4225          ENDIF
4226
4227          IF ( ALLOCATED ( surf_v(l)%mom_flux_w ) )  THEN
4228             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%mom_w',  surf_v(l)%mom_flux_w )
4229          ENDIF
4230
4231          IF ( ALLOCATED ( surf_v(l)%mom_flux_tke ) )  THEN
4232             CALL wrd_mpi_io_surface( 'surf_v(' // dum // ')%mom_tke', surf_v(l)%mom_flux_tke )
4233          ENDIF
4234
4235       ENDDO
4236
4237       CALL wrd_mpi_io_global_array( 'ns_h_on_file', ns_h_on_file )
4238       CALL wrd_mpi_io_global_array( 'ns_v_on_file', ns_v_on_file )
4239
4240    ENDIF
4241
4242 END SUBROUTINE surface_wrd_local
4243
4244
4245!--------------------------------------------------------------------------------------------------!
4246! Description:
4247! ------------
4248!> Reads surface-related restart data in Fortran binary format. Please note, restart data for a
4249!> certain surface orientation (e.g. horizontal upward-facing) is stored in one array, even if
4250!> surface elements may belong to different surface types natural or urban for example). Surface
4251!> elements are redistributed into its respective surface types within this routine. This allows
4252!> e.g. changing the surface type after reading the restart data, which might be required in case
4253!> of cyclic_fill mode.
4254!--------------------------------------------------------------------------------------------------!
4255 SUBROUTINE surface_rrd_local_ftn( kk, nxlf, nxlc, nxl_on_file, nxrf, nxr_on_file, nynf,           &
4256                                   nyn_on_file, nysf, nysc, nys_on_file, found )
4257
4258
4259    IMPLICIT NONE
4260
4261    INTEGER(iwp) ::  i            !< running index along x-direction, refers to former domain size
4262    INTEGER(iwp) ::  ic           !< running index along x-direction, refers to current domain size
4263    INTEGER(iwp) ::  j            !< running index along y-direction, refers to former domain size
4264    INTEGER(iwp) ::  jc           !< running index along y-direction, refers to former domain size
4265    INTEGER(iwp) ::  m            !< running index for surface elements, refers to gathered array encompassing all surface types
4266    INTEGER(iwp) ::  mm           !< running index for surface elements, refers to individual surface types
4267    INTEGER(iwp) ::  kk           !< running index over previous input files covering current local domain
4268    INTEGER(iwp) ::  nxlc         !< index of left boundary on current subdomain
4269    INTEGER(iwp) ::  nxlf         !< index of left boundary on former subdomain
4270    INTEGER(iwp) ::  nxl_on_file  !< index of left boundary on former local domain
4271    INTEGER(iwp) ::  nxrf         !< index of right boundary on former subdomain
4272    INTEGER(iwp) ::  nxr_on_file  !< index of right boundary on former local domain
4273    INTEGER(iwp) ::  nynf         !< index of north boundary on former subdomain
4274    INTEGER(iwp) ::  nyn_on_file  !< index of norht boundary on former local domain
4275    INTEGER(iwp) ::  nysc         !< index of south boundary on current subdomain
4276    INTEGER(iwp) ::  nysf         !< index of south boundary on former subdomain
4277    INTEGER(iwp) ::  nys_on_file  !< index of south boundary on former local domain
4278
4279    INTEGER(iwp), SAVE ::  l            !< index variable for surface type
4280
4281    LOGICAL ::  surf_match_def  !< flag indicating that surface element is of default type
4282    LOGICAL ::  surf_match_lsm  !< flag indicating that surface element is of natural type
4283    LOGICAL ::  surf_match_usm  !< flag indicating that surface element is of urban type
4284
4285    LOGICAL, INTENT(OUT) ::  found  !<
4286
4287    LOGICAL, SAVE ::  horizontal_surface  !< flag indicating horizontal surfaces
4288    LOGICAL, SAVE ::  vertical_surface    !< flag indicating vertical surfaces
4289
4290    TYPE(surf_type), DIMENSION(0:2), SAVE ::  surf_h  !< horizontal surface type on file
4291    TYPE(surf_type), DIMENSION(0:3), SAVE ::  surf_v  !< vertical surface type on file
4292
4293
4294    found = .TRUE.
4295
4296    SELECT CASE ( restart_string(1:length) )
4297!
4298!--    Read the number of horizontally orientated surface elements and  allocate arrays
4299       CASE ( 'ns_h_on_file' )
4300          IF ( kk == 1 )  THEN
4301             READ ( 13 )  ns_h_on_file
4302
4303             IF ( ALLOCATED( surf_h(0)%start_index ) )                                             &
4304                CALL deallocate_surface_attributes_h( surf_h(0) )
4305             IF ( ALLOCATED( surf_h(1)%start_index ) )                                             &
4306                CALL deallocate_surface_attributes_h( surf_h(1) )
4307             IF ( ALLOCATED( surf_h(2)%start_index ) )                                             &
4308                CALL deallocate_surface_attributes_h_top( surf_h(2) )
4309!
4310!--          Allocate memory for number of surface elements on file.
4311!--          Please note, this number is not necessarily the same as the final number of surface
4312!--          elements on local domain, which is the case if processor topology changes during
4313!--          restart runs.
4314!--          Horizontal upward facing
4315             surf_h(0)%ns = ns_h_on_file(0)
4316             CALL allocate_surface_attributes_h( surf_h(0), nys_on_file, nyn_on_file, nxl_on_file, &
4317                                                 nxr_on_file )
4318!
4319!--          Horizontal downward facing
4320             surf_h(1)%ns = ns_h_on_file(1)
4321             CALL allocate_surface_attributes_h( surf_h(1), nys_on_file, nyn_on_file, nxl_on_file, &
4322                                                 nxr_on_file )
4323!
4324!--          Model top
4325             surf_h(2)%ns = ns_h_on_file(2)
4326             CALL allocate_surface_attributes_h_top( surf_h(2), nys_on_file, nyn_on_file,          &
4327                                                     nxl_on_file, nxr_on_file )
4328
4329!
4330!--          Initial setting of flags for horizontal and vertical surfaces, will be set after start-
4331!--          and end-indices are read.
4332             horizontal_surface = .FALSE.
4333             vertical_surface   = .FALSE.
4334
4335          ENDIF
4336!
4337!--    Read the number of vertically orientated surface elements and allocate arrays
4338       CASE ( 'ns_v_on_file' )
4339          IF ( kk == 1 ) THEN
4340             READ ( 13 ) ns_v_on_file
4341
4342             DO  l = 0, 3
4343                IF ( ALLOCATED( surf_v(l)%start_index ) )                                          &
4344                   CALL deallocate_surface_attributes_v( surf_v(l) )
4345             ENDDO
4346
4347             DO  l = 0, 3
4348                surf_v(l)%ns = ns_v_on_file(l)
4349                CALL allocate_surface_attributes_v( surf_v(l), nys_on_file, nyn_on_file,           &
4350                                                    nxl_on_file, nxr_on_file )
4351            ENDDO
4352
4353          ENDIF
4354!
4355!--    Read start and end indices of surface elements at each (ji)-gridpoint
4356       CASE ( 'surf_h(0)%start_index' )
4357          IF ( kk == 1 )                                                                           &
4358             READ ( 13 ) surf_h(0)%start_index
4359          l = 0
4360       CASE ( 'surf_h(0)%end_index' )
4361          IF ( kk == 1 )                                                                           &
4362             READ ( 13 ) surf_h(0)%end_index
4363          horizontal_surface = .TRUE.
4364          vertical_surface   = .FALSE.
4365!
4366!--    Read specific attributes
4367       CASE ( 'surf_h(0)%us' )
4368          IF ( ALLOCATED( surf_h(0)%us )  .AND.  kk == 1 )                                         &
4369             READ ( 13 ) surf_h(0)%us
4370       CASE ( 'surf_h(0)%ts' )
4371          IF ( ALLOCATED( surf_h(0)%ts )  .AND.  kk == 1 )                                         &
4372             READ ( 13 ) surf_h(0)%ts
4373       CASE ( 'surf_h(0)%qs' )
4374          IF ( ALLOCATED( surf_h(0)%qs )  .AND.  kk == 1 )                                         &
4375             READ ( 13 ) surf_h(0)%qs
4376       CASE ( 'surf_h(0)%ss' )
4377          IF ( ALLOCATED( surf_h(0)%ss )  .AND.  kk == 1 )                                         &
4378             READ ( 13 ) surf_h(0)%ss
4379       CASE ( 'surf_h(0)%qcs' )
4380          IF ( ALLOCATED( surf_h(0)%qcs )  .AND.  kk == 1 )                                        &
4381             READ ( 13 ) surf_h(0)%qcs
4382       CASE ( 'surf_h(0)%ncs' )
4383          IF ( ALLOCATED( surf_h(0)%ncs )  .AND.  kk == 1 )                                        &
4384             READ ( 13 ) surf_h(0)%ncs
4385       CASE ( 'surf_h(0)%qis' )
4386          IF ( ALLOCATED( surf_h(0)%qis )  .AND.  kk == 1 )                                        &
4387             READ ( 13 ) surf_h(0)%qis
4388       CASE ( 'surf_h(0)%nis' )
4389          IF ( ALLOCATED( surf_h(0)%nis )  .AND.  kk == 1 )                                        &
4390             READ ( 13 ) surf_h(0)%nis
4391       CASE ( 'surf_h(0)%qrs' )
4392          IF ( ALLOCATED( surf_h(0)%qrs )  .AND.  kk == 1 )                                        &
4393             READ ( 13 ) surf_h(0)%qrs
4394       CASE ( 'surf_h(0)%nrs' )
4395          IF ( ALLOCATED( surf_h(0)%nrs )  .AND.  kk == 1 )                                        &
4396             READ ( 13 ) surf_h(0)%nrs
4397       CASE ( 'surf_h(0)%ol' )
4398          IF ( ALLOCATED( surf_h(0)%ol )  .AND.  kk == 1 )                                         &
4399             READ ( 13 ) surf_h(0)%ol
4400       CASE ( 'surf_h(0)%rib' )
4401          IF ( ALLOCATED( surf_h(0)%rib )  .AND.  kk == 1 )                                        &
4402             READ ( 13 ) surf_h(0)%rib
4403       CASE ( 'surf_h(0)%pt_surface' )
4404          IF ( ALLOCATED( surf_h(0)%pt_surface )  .AND.  kk == 1 )                                 &
4405             READ ( 13 ) surf_h(0)%pt_surface
4406       CASE ( 'surf_h(0)%q_surface' )
4407          IF ( ALLOCATED( surf_h(0)%q_surface )  .AND.  kk == 1 )                                  &
4408             READ ( 13 ) surf_h(0)%q_surface
4409       CASE ( 'surf_h(0)%vpt_surface' )
4410          IF ( ALLOCATED( surf_h(0)%vpt_surface )  .AND.  kk == 1 )                                &
4411             READ ( 13 ) surf_h(0)%vpt_surface
4412       CASE ( 'surf_h(0)%usws' )
4413          IF ( ALLOCATED( surf_h(0)%usws )  .AND.  kk == 1 )                                       &
4414             READ ( 13 ) surf_h(0)%usws
4415       CASE ( 'surf_h(0)%vsws' )
4416          IF ( ALLOCATED( surf_h(0)%vsws )  .AND.  kk == 1 )                                       &
4417             READ ( 13 ) surf_h(0)%vsws
4418       CASE ( 'surf_h(0)%shf' )
4419          IF ( ALLOCATED( surf_h(0)%shf )  .AND.  kk == 1 )                                        &
4420             READ ( 13 ) surf_h(0)%shf
4421       CASE ( 'surf_h(0)%qsws' )
4422          IF ( ALLOCATED( surf_h(0)%qsws )  .AND.  kk == 1 )                                       &
4423             READ ( 13 ) surf_h(0)%qsws
4424       CASE ( 'surf_h(0)%ssws' )
4425          IF ( ALLOCATED( surf_h(0)%ssws )  .AND.  kk == 1 )                                       &
4426             READ ( 13 ) surf_h(0)%ssws
4427       CASE ( 'surf_h(0)%css' )
4428          IF ( ALLOCATED( surf_h(0)%css )  .AND.  kk == 1 )                                        &
4429             READ ( 13 ) surf_h(0)%css
4430       CASE ( 'surf_h(0)%cssws' )
4431          IF ( ALLOCATED( surf_h(0)%cssws )  .AND.  kk == 1 )                                      &
4432             READ ( 13 ) surf_h(0)%cssws
4433       CASE ( 'surf_h(0)%qcsws' )
4434          IF ( ALLOCATED( surf_h(0)%qcsws )  .AND.  kk == 1 )                                      &
4435             READ ( 13 ) surf_h(0)%qcsws
4436       CASE ( 'surf_h(0)%ncsws' )
4437          IF ( ALLOCATED( surf_h(0)%ncsws )  .AND.  kk == 1 )                                      &
4438             READ ( 13 ) surf_h(0)%ncsws
4439       CASE ( 'surf_h(0)%qisws' )
4440          IF ( ALLOCATED( surf_h(0)%qisws )  .AND.  kk == 1 )                                      &
4441             READ ( 13 ) surf_h(0)%qisws
4442       CASE ( 'surf_h(0)%nisws' )
4443          IF ( ALLOCATED( surf_h(0)%nisws )  .AND.  kk == 1 )                                      &
4444             READ ( 13 ) surf_h(0)%nisws
4445       CASE ( 'surf_h(0)%qrsws' )
4446          IF ( ALLOCATED( surf_h(0)%qrsws )  .AND.  kk == 1 )                                      &
4447             READ ( 13 ) surf_h(0)%qrsws
4448       CASE ( 'surf_h(0)%nrsws' )
4449          IF ( ALLOCATED( surf_h(0)%nrsws )  .AND.  kk == 1 )                                      &
4450             READ ( 13 ) surf_h(0)%nrsws
4451       CASE ( 'surf_h(0)%sasws' )
4452          IF ( ALLOCATED( surf_h(0)%sasws )  .AND.  kk == 1 )                                      &
4453             READ ( 13 ) surf_h(0)%sasws
4454       CASE ( 'surf_h(1)%start_index' )
4455          IF ( kk == 1 )                                                                           &
4456             READ ( 13 ) surf_h(1)%start_index
4457          l = 1
4458       CASE ( 'surf_h(1)%end_index' )
4459          IF ( kk == 1 )                                                                           &
4460             READ ( 13 ) surf_h(1)%end_index
4461       CASE ( 'surf_h(1)%us' )
4462          IF ( ALLOCATED( surf_h(1)%us )  .AND.  kk == 1 )                                         &
4463             READ ( 13 ) surf_h(1)%us
4464       CASE ( 'surf_h(1)%ts' )
4465          IF ( ALLOCATED( surf_h(1)%ts )  .AND.  kk == 1 )                                         &
4466             READ ( 13 ) surf_h(1)%ts
4467       CASE ( 'surf_h(1)%qs' )
4468          IF ( ALLOCATED( surf_h(1)%qs )  .AND.  kk == 1 )                                         &
4469             READ ( 13 ) surf_h(1)%qs
4470       CASE ( 'surf_h(1)%ss' )
4471          IF ( ALLOCATED( surf_h(1)%ss )  .AND.  kk == 1 )                                         &
4472             READ ( 13 ) surf_h(1)%ss
4473       CASE ( 'surf_h(1)%qcs' )
4474          IF ( ALLOCATED( surf_h(1)%qcs )  .AND.  kk == 1 )                                        &
4475             READ ( 13 ) surf_h(1)%qcs
4476       CASE ( 'surf_h(1)%ncs' )
4477          IF ( ALLOCATED( surf_h(1)%ncs )  .AND.  kk == 1 )                                        &
4478             READ ( 13 ) surf_h(1)%ncs
4479       CASE ( 'surf_h(1)%qis' )
4480          IF ( ALLOCATED( surf_h(1)%qis )  .AND.  kk == 1 )                                        &
4481             READ ( 13 ) surf_h(1)%qis
4482       CASE ( 'surf_h(1)%nis' )
4483          IF ( ALLOCATED( surf_h(1)%nis )  .AND.  kk == 1 )                                        &
4484             READ ( 13 ) surf_h(1)%nis
4485       CASE ( 'surf_h(1)%qrs' )
4486          IF ( ALLOCATED( surf_h(1)%qrs )  .AND.  kk == 1 )                                        &
4487             READ ( 13 ) surf_h(1)%qrs
4488       CASE ( 'surf_h(1)%nrs' )
4489          IF ( ALLOCATED( surf_h(1)%nrs )  .AND.  kk == 1 )                                        &
4490             READ ( 13 ) surf_h(1)%nrs
4491       CASE ( 'surf_h(1)%ol' )
4492          IF ( ALLOCATED( surf_h(1)%ol )  .AND.  kk == 1 )                                         &
4493             READ ( 13 ) surf_h(1)%ol
4494       CASE ( 'surf_h(1)%rib' )
4495          IF ( ALLOCATED( surf_h(1)%rib )  .AND.  kk == 1 )                                        &
4496             READ ( 13 ) surf_h(1)%rib
4497       CASE ( 'surf_h(1)%pt_surface' )
4498          IF ( ALLOCATED( surf_h(1)%pt_surface )  .AND.  kk == 1 )                                 &
4499             READ ( 13 ) surf_h(1)%pt_surface
4500       CASE ( 'surf_h(1)%q_surface' )
4501          IF ( ALLOCATED( surf_h(1)%q_surface )  .AND.  kk == 1 )                                  &
4502             READ ( 13 ) surf_h(1)%q_surface
4503       CASE ( 'surf_h(1)%vpt_surface' )
4504          IF ( ALLOCATED( surf_h(1)%vpt_surface )  .AND.  kk == 1 )                                &
4505             READ ( 13 ) surf_h(1)%vpt_surface
4506       CASE ( 'surf_h(1)%usws' )
4507          IF ( ALLOCATED( surf_h(1)%usws )  .AND.  kk == 1 )                                       &
4508             READ ( 13 ) surf_h(1)%usws
4509       CASE ( 'surf_h(1)%vsws' )
4510          IF ( ALLOCATED( surf_h(1)%vsws )  .AND.  kk == 1 )                                       &
4511             READ ( 13 ) surf_h(1)%vsws
4512       CASE ( 'surf_h(1)%shf' )
4513          IF ( ALLOCATED( surf_h(1)%shf )  .AND.  kk == 1 )                                        &
4514             READ ( 13 ) surf_h(1)%shf
4515       CASE ( 'surf_h(1)%qsws' )
4516          IF ( ALLOCATED( surf_h(1)%qsws )  .AND.  kk == 1 )                                       &
4517             READ ( 13 ) surf_h(1)%qsws
4518       CASE ( 'surf_h(1)%ssws' )
4519          IF ( ALLOCATED( surf_h(1)%ssws )  .AND.  kk == 1 )                                       &
4520             READ ( 13 ) surf_h(1)%ssws
4521       CASE ( 'surf_h(1)%css' )
4522          IF ( ALLOCATED( surf_h(1)%css )  .AND.  kk == 1 )                                        &
4523             READ ( 13 ) surf_h(1)%css
4524       CASE ( 'surf_h(1)%cssws' )
4525          IF ( ALLOCATED( surf_h(1)%cssws )  .AND.  kk == 1 )                                      &
4526             READ ( 13 ) surf_h(1)%cssws
4527       CASE ( 'surf_h(1)%qcsws' )
4528          IF ( ALLOCATED( surf_h(1)%qcsws )  .AND.  kk == 1 )                                      &
4529             READ ( 13 ) surf_h(1)%qcsws
4530       CASE ( 'surf_h(1)%ncsws' )
4531          IF ( ALLOCATED( surf_h(1)%ncsws )  .AND.  kk == 1 )                                      &
4532             READ ( 13 ) surf_h(1)%ncsws
4533       CASE ( 'surf_h(1)%qisws' )
4534          IF ( ALLOCATED( surf_h(1)%qisws )  .AND.  kk == 1 )                                      &
4535             READ ( 13 ) surf_h(1)%qisws
4536       CASE ( 'surf_h(1)%nisws' )
4537          IF ( ALLOCATED( surf_h(1)%nisws )  .AND.  kk == 1 )                                      &
4538             READ ( 13 ) surf_h(1)%nisws
4539       CASE ( 'surf_h(1)%qrsws' )
4540          IF ( ALLOCATED( surf_h(1)%qrsws )  .AND.  kk == 1 )                                      &
4541             READ ( 13 ) surf_h(1)%qrsws
4542       CASE ( 'surf_h(1)%nrsws' )
4543          IF ( ALLOCATED( surf_h(1)%nrsws )  .AND.  kk == 1 )                                      &
4544             READ ( 13 ) surf_h(1)%nrsws
4545       CASE ( 'surf_h(1)%sasws' )
4546          IF ( ALLOCATED( surf_h(1)%sasws )  .AND.  kk == 1 )                                      &
4547             READ ( 13 ) surf_h(1)%sasws
4548       CASE ( 'surf_h(2)%start_index' )
4549          IF ( kk == 1 )                                                                           &
4550             READ ( 13 ) surf_h(2)%start_index
4551          l = 2
4552       CASE ( 'surf_h(2)%end_index' )
4553          IF ( kk == 1 )                                                                           &
4554             READ ( 13 ) surf_h(2)%end_index
4555       CASE ( 'surf_h(2)%us' )
4556          IF ( ALLOCATED( surf_h(2)%us )  .AND.  kk == 1 )                                         &
4557             READ ( 13 ) surf_h(2)%us
4558       CASE ( 'surf_h(2)%ts' )
4559          IF ( ALLOCATED( surf_h(2)%ts )  .AND.  kk == 1 )                                         &
4560             READ ( 13 ) surf_h(2)%ts
4561       CASE ( 'surf_h(2)%qs' )
4562          IF ( ALLOCATED( surf_h(2)%qs )  .AND.  kk == 1 )                                         &
4563             READ ( 13 ) surf_h(2)%qs
4564       CASE ( 'surf_h(2)%ss' )
4565          IF ( ALLOCATED( surf_h(2)%ss )  .AND.  kk == 1 )                                         &
4566             READ ( 13 ) surf_h(2)%ss
4567       CASE ( 'surf_h(2)%qcs' )
4568          IF ( ALLOCATED( surf_h(2)%qcs )  .AND.  kk == 1 )                                        &
4569             READ ( 13 ) surf_h(2)%qcs
4570       CASE ( 'surf_h(2)%ncs' )
4571          IF ( ALLOCATED( surf_h(2)%ncs )  .AND.  kk == 1 )                                        &
4572             READ ( 13 ) surf_h(2)%ncs
4573       CASE ( 'surf_h(2)%qis' )
4574          IF ( ALLOCATED( surf_h(2)%qis )  .AND.  kk == 1 )                                        &
4575             READ ( 13 ) surf_h(2)%qis
4576       CASE ( 'surf_h(2)%nis' )
4577          IF ( ALLOCATED( surf_h(2)%nis )  .AND.  kk == 1 )                                        &
4578             READ ( 13 ) surf_h(2)%nis
4579       CASE ( 'surf_h(2)%qrs' )
4580          IF ( ALLOCATED( surf_h(2)%qrs )  .AND.  kk == 1 )                                        &
4581             READ ( 13 ) surf_h(2)%qrs
4582       CASE ( 'surf_h(2)%nrs' )
4583          IF ( ALLOCATED( surf_h(2)%nrs )  .AND.  kk == 1 )                                        &
4584             READ ( 13 ) surf_h(2)%nrs
4585       CASE ( 'surf_h(2)%ol' )
4586          IF ( ALLOCATED( surf_h(2)%ol )  .AND.  kk == 1 )                                         &
4587             READ ( 13 ) surf_h(2)%ol
4588       CASE ( 'surf_h(2)%rib' )
4589          IF ( ALLOCATED( surf_h(2)%rib )  .AND.  kk == 1 )                                        &
4590             READ ( 13 ) surf_h(2)%rib
4591       CASE ( 'surf_h(2)%pt_surface' )
4592          IF ( ALLOCATED( surf_h(2)%pt_surface )  .AND.  kk == 1 )                                 &
4593             READ ( 13 ) surf_h(2)%pt_surface
4594       CASE ( 'surf_h(2)%q_surface' )
4595          IF ( ALLOCATED( surf_h(2)%q_surface )  .AND.  kk == 1 )                                  &
4596             READ ( 13 ) surf_h(2)%q_surface
4597       CASE ( 'surf_h(2)%vpt_surface' )
4598          IF ( ALLOCATED( surf_h(2)%vpt_surface )  .AND.  kk == 1 )                                &
4599             READ ( 13 ) surf_h(2)%vpt_surface
4600       CASE ( 'surf_h(2)%usws' )
4601          IF ( ALLOCATED( surf_h(2)%usws )  .AND.  kk == 1 )                                       &
4602             READ ( 13 ) surf_h(2)%usws
4603       CASE ( 'surf_h(2)%vsws' )
4604          IF ( ALLOCATED( surf_h(2)%vsws )  .AND.  kk == 1 )                                       &
4605             READ ( 13 ) surf_h(2)%vsws
4606       CASE ( 'surf_h(2)%shf' )
4607          IF ( ALLOCATED( surf_h(2)%shf )  .AND.  kk == 1 )                                        &
4608             READ ( 13 ) surf_h(2)%shf
4609       CASE ( 'surf_h(2)%qsws' )
4610          IF ( ALLOCATED( surf_h(2)%qsws )  .AND.  kk == 1 )                                       &
4611             READ ( 13 ) surf_h(2)%qsws
4612       CASE ( 'surf_h(2)%ssws' )
4613          IF ( ALLOCATED( surf_h(2)%ssws )  .AND.  kk == 1 )                                       &
4614             READ ( 13 ) surf_h(2)%ssws
4615       CASE ( 'surf_h(2)%css' )
4616          IF ( ALLOCATED( surf_h(2)%css )  .AND.  kk == 1 )                                        &
4617             READ ( 13 ) surf_h(2)%css
4618       CASE ( 'surf_h(2)%cssws' )
4619          IF ( ALLOCATED( surf_h(2)%cssws )  .AND.  kk == 1 )                                      &
4620             READ ( 13 ) surf_h(2)%cssws
4621       CASE ( 'surf_h(2)%qcsws' )
4622          IF ( ALLOCATED( surf_h(2)%qcsws )  .AND.  kk == 1 )                                      &
4623             READ ( 13 ) surf_h(2)%qcsws
4624       CASE ( 'surf_h(2)%ncsws' )
4625          IF ( ALLOCATED( surf_h(2)%ncsws )  .AND.  kk == 1 )                                      &
4626             READ ( 13 ) surf_h(2)%ncsws
4627       CASE ( 'surf_h(2)%qisws' )
4628          IF ( ALLOCATED( surf_h(2)%qisws )  .AND.  kk == 1 )                                      &
4629             READ ( 13 ) surf_h(2)%qisws
4630       CASE ( 'surf_h(2)%nisws' )
4631          IF ( ALLOCATED( surf_h(2)%nisws )  .AND.  kk == 1 )                                      &
4632             READ ( 13 ) surf_h(2)%nisws
4633       CASE ( 'surf_h(2)%qrsws' )
4634          IF ( ALLOCATED( surf_h(2)%qrsws )  .AND.  kk == 1 )                                      &
4635             READ ( 13 ) surf_h(2)%qrsws
4636       CASE ( 'surf_h(2)%nrsws' )
4637          IF ( ALLOCATED( surf_h(2)%nrsws )  .AND.  kk == 1 )                                      &
4638             READ ( 13 ) surf_h(2)%nrsws
4639       CASE ( 'surf_h(2)%sasws' )
4640          IF ( ALLOCATED( surf_h(2)%sasws )  .AND.  kk == 1 )                                      &
4641             READ ( 13 ) surf_h(2)%sasws
4642
4643       CASE ( 'surf_v(0)%start_index' )
4644          IF ( kk == 1 )                                                                           &
4645             READ ( 13 ) surf_v(0)%start_index
4646          l = 0
4647          horizontal_surface = .FALSE.
4648          vertical_surface   = .TRUE.
4649       CASE ( 'surf_v(0)%end_index' )
4650          IF ( kk == 1 )                                                                           &
4651             READ ( 13 ) surf_v(0)%end_index
4652       CASE ( 'surf_v(0)%us' )
4653          IF ( ALLOCATED( surf_v(0)%us )  .AND.  kk == 1 )                                         &
4654             READ ( 13 ) surf_v(0)%us
4655       CASE ( 'surf_v(0)%ts' )
4656          IF ( ALLOCATED( surf_v(0)%ts )  .AND.  kk == 1 )                                         &
4657             READ ( 13 ) surf_v(0)%ts
4658       CASE ( 'surf_v(0)%qs' )
4659          IF ( ALLOCATED( surf_v(0)%qs )  .AND.  kk == 1 )                                         &
4660             READ ( 13 ) surf_v(0)%qs
4661       CASE ( 'surf_v(0)%ss' )
4662          IF ( ALLOCATED( surf_v(0)%ss )  .AND.  kk == 1 )                                         &
4663             READ ( 13 ) surf_v(0)%ss
4664       CASE ( 'surf_v(0)%qcs' )
4665          IF ( ALLOCATED( surf_v(0)%qcs )  .AND.  kk == 1 )                                        &
4666             READ ( 13 ) surf_v(0)%qcs
4667       CASE ( 'surf_v(0)%ncs' )
4668          IF ( ALLOCATED( surf_v(0)%ncs )  .AND.  kk == 1 )                                        &
4669             READ ( 13 ) surf_v(0)%ncs
4670       CASE ( 'surf_v(0)%qis' )
4671          IF ( ALLOCATED( surf_v(0)%qis )  .AND.  kk == 1 )                                        &
4672             READ ( 13 ) surf_v(0)%qis
4673       CASE ( 'surf_v(0)%nis' )
4674          IF ( ALLOCATED( surf_v(0)%nis )  .AND.  kk == 1 )                                        &
4675             READ ( 13 ) surf_v(0)%nis
4676       CASE ( 'surf_v(0)%qrs' )
4677          IF ( ALLOCATED( surf_v(0)%qrs )  .AND.  kk == 1 )                                        &
4678             READ ( 13 ) surf_v(0)%qrs
4679       CASE ( 'surf_v(0)%nrs' )
4680          IF ( ALLOCATED( surf_v(0)%nrs )  .AND.  kk == 1 )                                        &
4681             READ ( 13 ) surf_v(0)%nrs
4682       CASE ( 'surf_v(0)%ol' )
4683          IF ( ALLOCATED( surf_v(0)%ol )  .AND.  kk == 1 )                                         &
4684             READ ( 13 ) surf_v(0)%ol
4685       CASE ( 'surf_v(0)%rib' )
4686          IF ( ALLOCATED( surf_v(0)%rib )  .AND.  kk == 1 )                                        &
4687             READ ( 13 ) surf_v(0)%rib
4688       CASE ( 'surf_v(0)%pt_surface' )
4689          IF ( ALLOCATED( surf_v(0)%pt_surface )  .AND.  kk == 1 )                                 &
4690             READ ( 13 ) surf_v(0)%pt_surface
4691       CASE ( 'surf_v(0)%q_surface' )
4692          IF ( ALLOCATED( surf_v(0)%q_surface )  .AND.  kk == 1 )                                  &
4693             READ ( 13 ) surf_v(0)%q_surface
4694       CASE ( 'surf_v(0)%vpt_surface' )
4695          IF ( ALLOCATED( surf_v(0)%vpt_surface )  .AND.  kk == 1 )                                &
4696             READ ( 13 ) surf_v(0)%vpt_surface
4697       CASE ( 'surf_v(0)%shf' )
4698          IF ( ALLOCATED( surf_v(0)%shf )  .AND.  kk == 1 )                                        &
4699             READ ( 13 ) surf_v(0)%shf
4700       CASE ( 'surf_v(0)%qsws' )
4701          IF ( ALLOCATED( surf_v(0)%qsws )  .AND.  kk == 1 )                                       &
4702             READ ( 13 ) surf_v(0)%qsws
4703       CASE ( 'surf_v(0)%ssws' )
4704          IF ( ALLOCATED( surf_v(0)%ssws )  .AND.  kk == 1 )                                       &
4705             READ ( 13 ) surf_v(0)%ssws
4706       CASE ( 'surf_v(0)%css' )
4707          IF ( ALLOCATED( surf_v(0)%css )  .AND.  kk == 1 )                                        &
4708             READ ( 13 ) surf_v(0)%css
4709       CASE ( 'surf_v(0)%cssws' )
4710          IF ( ALLOCATED( surf_v(0)%cssws )  .AND.  kk == 1 )                                      &
4711             READ ( 13 ) surf_v(0)%cssws
4712       CASE ( 'surf_v(0)%qcsws' )
4713          IF ( ALLOCATED( surf_v(0)%qcsws )  .AND.  kk == 1 )                                      &
4714             READ ( 13 ) surf_v(0)%qcsws
4715       CASE ( 'surf_v(0)%ncsws' )
4716          IF ( ALLOCATED( surf_v(0)%ncsws )  .AND.  kk == 1 )                                      &
4717             READ ( 13 ) surf_v(0)%ncsws
4718       CASE ( 'surf_v(0)%qisws' )
4719          IF ( ALLOCATED( surf_v(0)%qisws )  .AND.  kk == 1 )                                      &
4720             READ ( 13 ) surf_v(0)%qisws
4721       CASE ( 'surf_v(0)%nisws' )
4722          IF ( ALLOCATED( surf_v(0)%nisws )  .AND.  kk == 1 )                                      &
4723             READ ( 13 ) surf_v(0)%nisws
4724       CASE ( 'surf_v(0)%qrsws' )
4725          IF ( ALLOCATED( surf_v(0)%qrsws )  .AND.  kk == 1 )                                      &
4726             READ ( 13 ) surf_v(0)%qrsws
4727       CASE ( 'surf_v(0)%nrsws' )
4728          IF ( ALLOCATED( surf_v(0)%nrsws )  .AND.  kk == 1 )                                      &
4729             READ ( 13 ) surf_v(0)%nrsws
4730       CASE ( 'surf_v(0)%sasws' )
4731          IF ( ALLOCATED( surf_v(0)%sasws )  .AND.  kk == 1 )                                      &
4732             READ ( 13 ) surf_v(0)%sasws
4733       CASE ( 'surf_v(0)%mom_uv' )
4734          IF ( ALLOCATED( surf_v(0)%mom_flux_uv )  .AND.  kk == 1 )                                &
4735             READ ( 13 ) surf_v(0)%mom_flux_uv
4736       CASE ( 'surf_v(0)%mom_w' )
4737          IF ( ALLOCATED( surf_v(0)%mom_flux_w )  .AND.  kk == 1 )                                 &
4738             READ ( 13 ) surf_v(0)%mom_flux_w
4739       CASE ( 'surf_v(0)%mom_tke' )
4740          IF ( ALLOCATED( surf_v(0)%mom_flux_tke )  .AND.  kk == 1 )                               &
4741             READ ( 13 ) surf_v(0)%mom_flux_tke
4742       CASE ( 'surf_v(1)%start_index' )
4743          IF ( kk == 1 )                                                                           &
4744             READ ( 13 ) surf_v(1)%start_index
4745          l = 1
4746       CASE ( 'surf_v(1)%end_index' )
4747          IF ( kk == 1 )                                                                           &
4748             READ ( 13 ) surf_v(1)%end_index
4749       CASE ( 'surf_v(1)%us' )
4750          IF ( ALLOCATED( surf_v(1)%us )  .AND.  kk == 1 )                                         &
4751             READ ( 13 ) surf_v(1)%us
4752       CASE ( 'surf_v(1)%ts' )
4753          IF ( ALLOCATED( surf_v(1)%ts )  .AND.  kk == 1 )                                         &
4754             READ ( 13 ) surf_v(1)%ts
4755       CASE ( 'surf_v(1)%qs' )
4756          IF ( ALLOCATED( surf_v(1)%qs )  .AND.  kk == 1 )                                         &
4757             READ ( 13 ) surf_v(1)%qs
4758       CASE ( 'surf_v(1)%ss' )
4759          IF ( ALLOCATED( surf_v(1)%ss )  .AND.  kk == 1 )                                         &
4760             READ ( 13 ) surf_v(1)%ss
4761       CASE ( 'surf_v(1)%qcs' )
4762          IF ( ALLOCATED( surf_v(1)%qcs )  .AND.  kk == 1 )                                        &
4763             READ ( 13 ) surf_v(1)%qcs
4764       CASE ( 'surf_v(1)%ncs' )
4765          IF ( ALLOCATED( surf_v(1)%ncs )  .AND.  kk == 1 )                                        &
4766             READ ( 13 ) surf_v(1)%ncs
4767       CASE ( 'surf_v(1)%qis' )
4768          IF ( ALLOCATED( surf_v(1)%qis )  .AND.  kk == 1 )                                        &
4769             READ ( 13 ) surf_v(1)%qis
4770       CASE ( 'surf_v(1)%nis' )
4771          IF ( ALLOCATED( surf_v(1)%nis )  .AND.  kk == 1 )                                        &
4772             READ ( 13 ) surf_v(1)%nis
4773       CASE ( 'surf_v(1)%qrs' )
4774          IF ( ALLOCATED( surf_v(1)%qrs )  .AND.  kk == 1 )                                        &
4775             READ ( 13 ) surf_v(1)%qrs
4776       CASE ( 'surf_v(1)%nrs' )
4777          IF ( ALLOCATED( surf_v(1)%nrs )  .AND.  kk == 1 )                                        &
4778             READ ( 13 ) surf_v(1)%nrs
4779       CASE ( 'surf_v(1)%ol' )
4780          IF ( ALLOCATED( surf_v(1)%ol )  .AND.  kk == 1 )                                         &
4781             READ ( 13 ) surf_v(1)%ol
4782       CASE ( 'surf_v(1)%rib' )
4783          IF ( ALLOCATED( surf_v(1)%rib )  .AND.  kk == 1 )                                        &
4784             READ ( 13 ) surf_v(1)%rib
4785       CASE ( 'surf_v(1)%pt_surface' )
4786          IF ( ALLOCATED( surf_v(1)%pt_surface )  .AND.  kk == 1 )                                 &
4787             READ ( 13 ) surf_v(1)%pt_surface
4788       CASE ( 'surf_v(1)%q_surface' )
4789          IF ( ALLOCATED( surf_v(1)%q_surface )  .AND.  kk == 1 )                                  &
4790             READ ( 13 ) surf_v(1)%q_surface
4791       CASE ( 'surf_v(1)%vpt_surface' )
4792          IF ( ALLOCATED( surf_v(1)%vpt_surface )  .AND.  kk == 1 )                                &
4793             READ ( 13 ) surf_v(1)%vpt_surface
4794       CASE ( 'surf_v(1)%shf' )
4795          IF ( ALLOCATED( surf_v(1)%shf )  .AND.  kk == 1 )                                        &
4796             READ ( 13 ) surf_v(1)%shf
4797       CASE ( 'surf_v(1)%qsws' )
4798          IF ( ALLOCATED( surf_v(1)%qsws )  .AND.  kk == 1 )                                       &
4799             READ ( 13 ) surf_v(1)%qsws
4800       CASE ( 'surf_v(1)%ssws' )
4801          IF ( ALLOCATED( surf_v(1)%ssws )  .AND.  kk == 1 )                                       &
4802             READ ( 13 ) surf_v(1)%ssws
4803       CASE ( 'surf_v(1)%css' )
4804          IF ( ALLOCATED( surf_v(1)%css )  .AND.  kk == 1 )                                        &
4805             READ ( 13 ) surf_v(1)%css
4806       CASE ( 'surf_v(1)%cssws' )
4807          IF ( ALLOCATED( surf_v(1)%cssws )  .AND.  kk == 1 )                                      &
4808             READ ( 13 ) surf_v(1)%cssws
4809       CASE ( 'surf_v(1)%qcsws' )
4810          IF ( ALLOCATED( surf_v(1)%qcsws )  .AND.  kk == 1 )                                      &
4811             READ ( 13 ) surf_v(1)%qcsws
4812       CASE ( 'surf_v(1)%ncsws' )
4813          IF ( ALLOCATED( surf_v(1)%ncsws )  .AND.  kk == 1 )                                      &
4814             READ ( 13 ) surf_v(1)%ncsws
4815       CASE ( 'surf_v(1)%qisws' )
4816          IF ( ALLOCATED( surf_v(1)%qisws )  .AND.  kk == 1 )                                      &
4817             READ ( 13 ) surf_v(1)%qisws
4818       CASE ( 'surf_v(1)%nisws' )
4819          IF ( ALLOCATED( surf_v(1)%nisws )  .AND.  kk == 1 )                                      &
4820             READ ( 13 ) surf_v(1)%nisws
4821       CASE ( 'surf_v(1)%qrsws' )
4822          IF ( ALLOCATED( surf_v(1)%qrsws )  .AND.  kk == 1 )                                      &
4823             READ ( 13 ) surf_v(1)%qrsws
4824       CASE ( 'surf_v(1)%nrsws' )
4825          IF ( ALLOCATED( surf_v(1)%nrsws )  .AND.  kk == 1 )                                      &
4826             READ ( 13 ) surf_v(1)%nrsws
4827       CASE ( 'surf_v(1)%sasws' )
4828          IF ( ALLOCATED( surf_v(1)%sasws )  .AND.  kk == 1 )                                      &
4829             READ ( 13 ) surf_v(1)%sasws
4830       CASE ( 'surf_v(1)%mom_uv' )
4831          IF ( ALLOCATED( surf_v(1)%mom_flux_uv )  .AND.  kk == 1 )                                &
4832             READ ( 13 ) surf_v(1)%mom_flux_uv
4833       CASE ( 'surf_v(1)%mom_w' )
4834          IF ( ALLOCATED( surf_v(1)%mom_flux_w )  .AND.  kk == 1 )                                 &
4835             READ ( 13 ) surf_v(1)%mom_flux_w
4836       CASE ( 'surf_v(1)%mom_tke' )
4837          IF ( ALLOCATED( surf_v(1)%mom_flux_tke )  .AND.  kk == 1 )                               &
4838             READ ( 13 ) surf_v(1)%mom_flux_tke
4839       CASE ( 'surf_v(2)%start_index' )
4840          IF ( kk == 1 )                                                                           &
4841             READ ( 13 ) surf_v(2)%start_index
4842          l = 2
4843       CASE ( 'surf_v(2)%end_index' )
4844          IF ( kk == 1 )                                                                           &
4845             READ ( 13 ) surf_v(2)%end_index
4846       CASE ( 'surf_v(2)%us' )
4847          IF ( ALLOCATED( surf_v(2)%us )  .AND.  kk == 1 )                                         &
4848             READ ( 13 ) surf_v(2)%us
4849       CASE ( 'surf_v(2)%ts' )
4850          IF ( ALLOCATED( surf_v(2)%ts )  .AND.  kk == 1 )                                         &
4851             READ ( 13 ) surf_v(2)%ts
4852       CASE ( 'surf_v(2)%qs' )
4853          IF ( ALLOCATED( surf_v(2)%qs )  .AND.  kk == 1 )                                         &
4854             READ ( 13 ) surf_v(2)%qs
4855       CASE ( 'surf_v(2)%ss' )
4856          IF ( ALLOCATED( surf_v(2)%ss )  .AND.  kk == 1 )                                         &
4857             READ ( 13 ) surf_v(2)%ss
4858       CASE ( 'surf_v(2)%qcs' )
4859          IF ( ALLOCATED( surf_v(2)%qcs )  .AND.  kk == 1 )                                        &
4860             READ ( 13 ) surf_v(2)%qcs
4861       CASE ( 'surf_v(2)%ncs' )
4862          IF ( ALLOCATED( surf_v(2)%ncs )  .AND.  kk == 1 )                                        &
4863             READ ( 13 ) surf_v(2)%ncs
4864       CASE ( 'surf_v(2)%qis' )
4865          IF ( ALLOCATED( surf_v(2)%qis )  .AND.  kk == 1 )                                        &
4866             READ ( 13 ) surf_v(2)%qis
4867       CASE ( 'surf_v(2)%nis' )
4868          IF ( ALLOCATED( surf_v(2)%nis )  .AND.  kk == 1 )                                        &
4869             READ ( 13 ) surf_v(2)%nis
4870       CASE ( 'surf_v(2)%qrs' )
4871          IF ( ALLOCATED( surf_v(2)%qrs )  .AND.  kk == 1 )                                        &
4872             READ ( 13 ) surf_v(2)%qrs
4873       CASE ( 'surf_v(2)%nrs' )
4874          IF ( ALLOCATED( surf_v(2)%nrs )  .AND.  kk == 1 )                                        &
4875             READ ( 13 ) surf_v(2)%nrs
4876       CASE ( 'surf_v(2)%ol' )
4877          IF ( ALLOCATED( surf_v(2)%ol )  .AND.  kk == 1 )                                         &
4878             READ ( 13 ) surf_v(2)%ol
4879       CASE ( 'surf_v(2)%rib' )
4880          IF ( ALLOCATED( surf_v(2)%rib )  .AND.  kk == 1 )                                        &
4881             READ ( 13 ) surf_v(2)%rib
4882       CASE ( 'surf_v(2)%pt_surface' )
4883          IF ( ALLOCATED( surf_v(2)%pt_surface )  .AND.  kk == 1 )                                 &
4884             READ ( 13 ) surf_v(2)%pt_surface
4885       CASE ( 'surf_v(2)%q_surface' )
4886          IF ( ALLOCATED( surf_v(2)%q_surface )  .AND.  kk == 1 )                                  &
4887             READ ( 13 ) surf_v(2)%q_surface
4888       CASE ( 'surf_v(2)%vpt_surface' )
4889          IF ( ALLOCATED( surf_v(2)%vpt_surface )  .AND.  kk == 1 )                                &
4890             READ ( 13 ) surf_v(2)%vpt_surface
4891       CASE ( 'surf_v(2)%shf' )
4892          IF ( ALLOCATED( surf_v(2)%shf )  .AND.  kk == 1 )                                        &
4893             READ ( 13 ) surf_v(2)%shf
4894       CASE ( 'surf_v(2)%qsws' )
4895          IF ( ALLOCATED( surf_v(2)%qsws )  .AND.  kk == 1 )                                       &
4896             READ ( 13 ) surf_v(2)%qsws
4897       CASE ( 'surf_v(2)%ssws' )
4898          IF ( ALLOCATED( surf_v(2)%ssws )  .AND.  kk == 1 )                                       &
4899             READ ( 13 ) surf_v(2)%ssws
4900       CASE ( 'surf_v(2)%css' )
4901          IF ( ALLOCATED( surf_v(2)%css )  .AND.  kk == 1 )                                        &
4902             READ ( 13 ) surf_v(2)%css
4903       CASE ( 'surf_v(2)%cssws' )
4904          IF ( ALLOCATED( surf_v(2)%cssws )  .AND.  kk == 1 )                                      &
4905             READ ( 13 ) surf_v(2)%cssws
4906       CASE ( 'surf_v(2)%qcsws' )
4907          IF ( ALLOCATED( surf_v(2)%qcsws )  .AND.  kk == 1 )                                      &
4908             READ ( 13 ) surf_v(2)%qcsws
4909       CASE ( 'surf_v(2)%ncsws' )
4910          IF ( ALLOCATED( surf_v(2)%ncsws )  .AND.  kk == 1 )                                      &
4911             READ ( 13 ) surf_v(2)%ncsws
4912       CASE ( 'surf_v(2)%qisws' )
4913          IF ( ALLOCATED( surf_v(2)%qisws )  .AND.  kk == 1 )                                      &
4914             READ ( 13 ) surf_v(2)%qisws
4915       CASE ( 'surf_v(2)%nisws' )
4916          IF ( ALLOCATED( surf_v(2)%nisws )  .AND.  kk == 1 )                                      &
4917             READ ( 13 ) surf_v(2)%nisws
4918       CASE ( 'surf_v(2)%qrsws' )
4919          IF ( ALLOCATED( surf_v(2)%qrsws )  .AND.  kk == 1 )                                      &
4920             READ ( 13 ) surf_v(2)%qrsws
4921       CASE ( 'surf_v(2)%nrsws' )
4922          IF ( ALLOCATED( surf_v(2)%nrsws )  .AND.  kk == 1 )                                      &
4923             READ ( 13 ) surf_v(2)%nrsws
4924       CASE ( 'surf_v(2)%sasws' )
4925          IF ( ALLOCATED( surf_v(2)%sasws )  .AND.  kk == 1 )                                      &
4926             READ ( 13 ) surf_v(2)%sasws
4927       CASE ( 'surf_v(2)%mom_uv' )
4928          IF ( ALLOCATED( surf_v(2)%mom_flux_uv )  .AND.  kk == 1 )                                &
4929             READ ( 13 ) surf_v(2)%mom_flux_uv
4930       CASE ( 'surf_v(2)%mom_w' )
4931          IF ( ALLOCATED( surf_v(2)%mom_flux_w )  .AND.  kk == 1 )                                 &
4932             READ ( 13 ) surf_v(2)%mom_flux_w
4933       CASE ( 'surf_v(2)%mom_tke' )
4934          IF ( ALLOCATED( surf_v(2)%mom_flux_tke )  .AND.  kk == 1 )                               &
4935             READ ( 13 ) surf_v(2)%mom_flux_tke
4936       CASE ( 'surf_v(3)%start_index' )
4937          IF ( kk == 1 )                                                                           &
4938             READ ( 13 ) surf_v(3)%start_index
4939          l = 3
4940       CASE ( 'surf_v(3)%end_index' )
4941          IF ( kk == 1 )                                                                           &
4942             READ ( 13 ) surf_v(3)%end_index
4943       CASE ( 'surf_v(3)%us' )
4944          IF ( ALLOCATED( surf_v(3)%us )  .AND.  kk == 1 )                                         &
4945             READ ( 13 ) surf_v(3)%us
4946       CASE ( 'surf_v(3)%ts' )
4947          IF ( ALLOCATED( surf_v(3)%ts )  .AND.  kk == 1 )                                         &
4948             READ ( 13 ) surf_v(3)%ts
4949       CASE ( 'surf_v(3)%qs' )
4950          IF ( ALLOCATED( surf_v(3)%qs )  .AND.  kk == 1 )                                         &
4951             READ ( 13 ) surf_v(3)%qs
4952       CASE ( 'surf_v(3)%ss' )
4953          IF ( ALLOCATED( surf_v(3)%ss )  .AND.  kk == 1 )                                         &
4954             READ ( 13 ) surf_v(3)%ss
4955       CASE ( 'surf_v(3)%qcs' )
4956          IF ( ALLOCATED( surf_v(3)%qcs )  .AND.  kk == 1 )                                        &
4957             READ ( 13 ) surf_v(3)%qcs
4958       CASE ( 'surf_v(3)%ncs' )
4959          IF ( ALLOCATED( surf_v(3)%ncs )  .AND.  kk == 1 )                                        &
4960             READ ( 13 ) surf_v(3)%ncs
4961       CASE ( 'surf_v(3)%qis' )
4962          IF ( ALLOCATED( surf_v(3)%qis )  .AND.  kk == 1 )                                        &
4963             READ ( 13 ) surf_v(3)%qis
4964       CASE ( 'surf_v(3)%nis' )
4965          IF ( ALLOCATED( surf_v(3)%nis )  .AND.  kk == 1 )                                        &
4966             READ ( 13 ) surf_v(3)%nis
4967       CASE ( 'surf_v(3)%qrs' )
4968          IF ( ALLOCATED( surf_v(3)%qrs )  .AND.  kk == 1 )                                        &
4969             READ ( 13 ) surf_v(3)%qrs
4970       CASE ( 'surf_v(3)%nrs' )
4971          IF ( ALLOCATED( surf_v(3)%nrs )  .AND.  kk == 1 )                                        &
4972             READ ( 13 ) surf_v(3)%nrs
4973       CASE ( 'surf_v(3)%ol' )
4974          IF ( ALLOCATED( surf_v(3)%ol )  .AND.  kk == 1 )                                         &
4975             READ ( 13 ) surf_v(3)%ol
4976       CASE ( 'surf_v(3)%rib' )
4977          IF ( ALLOCATED( surf_v(3)%rib )  .AND.  kk == 1 )                                        &
4978             READ ( 13 ) surf_v(3)%rib
4979       CASE ( 'surf_v(3)%pt_surface' )
4980          IF ( ALLOCATED( surf_v(3)%pt_surface )  .AND.  kk == 1 )                                 &
4981             READ ( 13 ) surf_v(3)%pt_surface
4982       CASE ( 'surf_v(3)%q_surface' )
4983          IF ( ALLOCATED( surf_v(3)%q_surface )  .AND.  kk == 1 )                                  &
4984             READ ( 13 ) surf_v(3)%q_surface
4985       CASE ( 'surf_v(3)%vpt_surface' )
4986          IF ( ALLOCATED( surf_v(3)%vpt_surface )  .AND.  kk == 1 )                                &
4987             READ ( 13 ) surf_v(3)%vpt_surface
4988       CASE ( 'surf_v(3)%shf' )
4989          IF ( ALLOCATED( surf_v(3)%shf )  .AND.  kk == 1 )                                        &
4990             READ ( 13 ) surf_v(3)%shf
4991       CASE ( 'surf_v(3)%qsws' )
4992          IF ( ALLOCATED( surf_v(3)%qsws )  .AND.  kk == 1 )                                       &
4993             READ ( 13 ) surf_v(3)%qsws
4994       CASE ( 'surf_v(3)%ssws' )
4995          IF ( ALLOCATED( surf_v(3)%ssws )  .AND.  kk == 1 )                                       &
4996             READ ( 13 ) surf_v(3)%ssws
4997       CASE ( 'surf_v(3)%css' )
4998          IF ( ALLOCATED( surf_v(3)%css )  .AND.  kk == 1 )                                        &
4999             READ ( 13 ) surf_v(3)%css
5000       CASE ( 'surf_v(3)%cssws' )
5001          IF ( ALLOCATED( surf_v(3)%cssws )  .AND.  kk == 1 )                                      &
5002             READ ( 13 ) surf_v(3)%cssws
5003       CASE ( 'surf_v(3)%qcsws' )
5004          IF ( ALLOCATED( surf_v(3)%qcsws )  .AND.  kk == 1 )                                      &
5005             READ ( 13 ) surf_v(3)%qcsws
5006       CASE ( 'surf_v(3)%ncsws' )
5007          IF ( ALLOCATED( surf_v(3)%ncsws )  .AND.  kk == 1 )                                      &
5008             READ ( 13 ) surf_v(3)%ncsws
5009       CASE ( 'surf_v(3)%qisws' )
5010          IF ( ALLOCATED( surf_v(3)%qisws )  .AND.  kk == 1 )                                      &
5011             READ ( 13 ) surf_v(3)%qisws
5012       CASE ( 'surf_v(3)%nisws' )
5013          IF ( ALLOCATED( surf_v(3)%nisws )  .AND.  kk == 1 )                                      &
5014             READ ( 13 ) surf_v(3)%nisws
5015       CASE ( 'surf_v(3)%qrsws' )
5016          IF ( ALLOCATED( surf_v(3)%qrsws )  .AND.  kk == 1 )                                      &
5017             READ ( 13 ) surf_v(3)%qrsws
5018       CASE ( 'surf_v(3)%nrsws' )
5019          IF ( ALLOCATED( surf_v(3)%nrsws )  .AND.  kk == 1 )                                      &
5020             READ ( 13 ) surf_v(3)%nrsws
5021       CASE ( 'surf_v(3)%sasws' )
5022          IF ( ALLOCATED( surf_v(3)%sasws )  .AND.  kk == 1 )                                      &
5023             READ ( 13 ) surf_v(3)%sasws
5024       CASE ( 'surf_v(3)%mom_uv' )
5025          IF ( ALLOCATED( surf_v(3)%mom_flux_uv )  .AND.  kk == 1 )                                &
5026             READ ( 13 ) surf_v(3)%mom_flux_uv
5027       CASE ( 'surf_v(3)%mom_w' )
5028          IF ( ALLOCATED( surf_v(3)%mom_flux_w )  .AND.  kk == 1 )                                 &
5029             READ ( 13 ) surf_v(3)%mom_flux_w
5030       CASE ( 'surf_v(3)%mom_tke' )
5031          IF ( ALLOCATED( surf_v(3)%mom_flux_tke )  .AND.  kk == 1 )                               &
5032             READ ( 13 ) surf_v(3)%mom_flux_tke
5033
5034       CASE DEFAULT
5035
5036             found = .FALSE.
5037
5038    END SELECT
5039!
5040!-- Redistribute surface elements on its respective type. Start with horizontally orientated surfaces.
5041    IF ( horizontal_surface  .AND.                                                                 &
5042         .NOT. INDEX( restart_string(1:length), '%start_index' ) /= 0 )                            &
5043    THEN
5044
5045       ic = nxlc
5046       DO  i = nxlf, nxrf
5047          jc = nysc
5048          DO  j = nysf, nynf
5049!
5050!--          Determine type of surface element, i.e. default, natural, urban, at current grid point.
5051             surf_match_def  = surf_def_h(l)%end_index(jc,ic) >= surf_def_h(l)%start_index(jc,ic)
5052             IF ( l < 2 ) THEN
5053                surf_match_lsm  = surf_lsm_h(l)%end_index(jc,ic) >= surf_lsm_h(l)%start_index(jc,ic)
5054                surf_match_usm  = surf_usm_h(l)%end_index(jc,ic) >= surf_usm_h(l)%start_index(jc,ic)
5055             ELSE
5056                surf_match_lsm  = .FALSE.
5057                surf_match_usm  = .FALSE.
5058             ENDIF
5059!
5060!--          Write restart data onto default-type surfaces if required.
5061             IF ( surf_match_def )  THEN
5062!
5063!--             Set the start index for the local surface element
5064                mm = surf_def_h(l)%start_index(jc,ic)
5065!
5066!--             For index pair (j,i) on file loop from start to end index, and in case the local
5067!--             surface element mm is smaller than the local end index, assign the respective
5068!--             surface data to this element.
5069                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
5070                   IF ( surf_def_h(l)%end_index(jc,ic) >= mm )                                     &
5071                      CALL restore_surface_elements( surf_def_h(l), mm, surf_h(l), m )
5072                   mm = mm + 1
5073                ENDDO
5074             ENDIF
5075!
5076!--          Same for natural-type surfaces. Please note, it is implicitly assumed that natural
5077!--          surface elements are below urban surface elements if there are several horizontal
5078!--          surfaces at (j,i). An example would be bridges.
5079             IF ( surf_match_lsm )  THEN
5080                mm = surf_lsm_h(l)%start_index(jc,ic)
5081                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
5082                   IF ( surf_lsm_h(l)%end_index(jc,ic) >= mm )                                        &
5083                      CALL restore_surface_elements( surf_lsm_h(l), mm, surf_h(l), m )
5084                   mm = mm + 1
5085                ENDDO
5086             ENDIF
5087!
5088!--          Same for urban-type surfaces
5089             IF ( surf_match_usm )  THEN
5090                mm = surf_usm_h(l)%start_index(jc,ic)
5091                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
5092                   IF ( surf_usm_h(l)%end_index(jc,ic) >= mm )                                        &
5093                      CALL restore_surface_elements( surf_usm_h(l), mm, surf_h(l), m )
5094                   mm = mm + 1
5095                ENDDO
5096             ENDIF
5097
5098             jc = jc + 1
5099          ENDDO
5100          ic = ic + 1
5101       ENDDO
5102    ELSEIF ( vertical_surface  .AND.                                                               &
5103             .NOT. INDEX( restart_string(1:length), '%start_index' ) /= 0 )  THEN
5104       ic = nxlc
5105       DO  i = nxlf, nxrf
5106          jc = nysc
5107          DO  j = nysf, nynf
5108!
5109!--          Determine type of surface element, i.e. default, natural, urban, at current grid point.
5110             surf_match_def = surf_def_v(l)%end_index(jc,ic) >= surf_def_v(l)%start_index(jc,ic)
5111             surf_match_lsm = surf_lsm_v(l)%end_index(jc,ic) >= surf_lsm_v(l)%start_index(jc,ic)
5112             surf_match_usm = surf_usm_v(l)%end_index(jc,ic) >= surf_usm_v(l)%start_index(jc,ic)
5113!
5114!--          Write restart data onto default-type surfaces if required.
5115             IF ( surf_match_def )  THEN
5116!
5117!--             Set the start index for the local surface element
5118                mm = surf_def_v(l)%start_index(jc,ic)
5119!
5120!--             For index pair (j,i) on file loop from start to end index, and in case the local
5121!--             surface element mm is smaller than the local end index, assign the respective
5122!--             surface data to this element.
5123                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
5124                   IF ( surf_def_v(l)%end_index(jc,ic) >= mm )                                     &
5125                      CALL restore_surface_elements( surf_def_v(l), mm, surf_v(l), m )
5126                   mm = mm + 1
5127                ENDDO
5128             ENDIF
5129!
5130!--          Same for natural-type surfaces. Please note, it is implicitly assumed that natural
5131!--          surface elements are below urban surface elements if there are several vertical
5132!--          surfaces at (j,i). An example a terrain elevations with a building on top. So far,
5133!--          initialization of urban surfaces below natural surfaces on the same (j,i) is not
5134!--          possible, so that this case cannot occur.
5135             IF ( surf_match_lsm )  THEN
5136                mm = surf_lsm_v(l)%start_index(jc,ic)
5137                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
5138                   IF ( surf_lsm_v(l)%end_index(jc,ic) >= mm )                                     &
5139                      CALL restore_surface_elements( surf_lsm_v(l), mm, surf_v(l), m )
5140                   mm = mm + 1
5141                ENDDO
5142             ENDIF
5143
5144             IF ( surf_match_usm )  THEN
5145                mm = surf_usm_v(l)%start_index(jc,ic)
5146                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
5147                   IF ( surf_usm_v(l)%end_index(jc,ic) >= mm )                                     &
5148                      CALL restore_surface_elements( surf_usm_v(l), mm, surf_v(l), m )
5149                   mm = mm + 1
5150                ENDDO
5151             ENDIF
5152
5153             jc = jc + 1
5154          ENDDO
5155          ic = ic + 1
5156       ENDDO
5157    ENDIF
5158
5159 CONTAINS
5160
5161
5162!--------------------------------------------------------------------------------------------------!
5163! Description:
5164! ------------
5165!> Restores surface elements back on its respective type.
5166!--------------------------------------------------------------------------------------------------!
5167 SUBROUTINE restore_surface_elements( surf_target, m_target, surf_file, m_file )
5168
5169    IMPLICIT NONE
5170
5171    INTEGER(iwp) ::  m_file    !< respective surface-element index of current surface array
5172    INTEGER(iwp) ::  m_target  !< respecitve surface-element index of surface array on file
5173    INTEGER(iwp) ::  lsp       !< running index chemical species
5174
5175    TYPE(surf_type) ::  surf_target  !< target surface type
5176    TYPE(surf_type) ::  surf_file    !< surface type on file
5177
5178
5179    IF ( INDEX( restart_string(1:length), '%us' ) /= 0 )  THEN
5180       IF ( ALLOCATED( surf_target%us )  .AND.  ALLOCATED( surf_file%us ) )                        &
5181          surf_target%us(m_target) = surf_file%us(m_file)
5182    ENDIF
5183
5184    IF ( INDEX( restart_string(1:length), '%ol' ) /= 0 )  THEN
5185       IF ( ALLOCATED( surf_target%ol )  .AND.  ALLOCATED( surf_file%ol ) )                        &
5186          surf_target%ol(m_target) = surf_file%ol(m_file)
5187    ENDIF
5188
5189    IF ( INDEX( restart_string(1:length), '%pt_surface' ) /= 0 )  THEN
5190       IF ( ALLOCATED( surf_target%pt_surface )  .AND.  ALLOCATED( surf_file%pt_surface ) )        &
5191          surf_target%pt_surface(m_target) = surf_file%pt_surface(m_file)
5192    ENDIF
5193
5194    IF ( INDEX( restart_string(1:length), '%q_surface' ) /= 0 )  THEN
5195       IF ( ALLOCATED( surf_target%q_surface )  .AND.  ALLOCATED( surf_file%q_surface ) )          &
5196          surf_target%q_surface(m_target) = surf_file%q_surface(m_file)
5197    ENDIF
5198
5199    IF ( INDEX( restart_string(1:length), '%vpt_surface' ) /= 0 )  THEN
5200       IF ( ALLOCATED( surf_target%vpt_surface )  .AND.  ALLOCATED( surf_file%vpt_surface ) )      &
5201          surf_target%vpt_surface(m_target) = surf_file%vpt_surface(m_file)
5202    ENDIF
5203
5204    IF ( INDEX( restart_string(1:length), '%usws' ) /= 0 )  THEN
5205       IF ( ALLOCATED( surf_target%usws )  .AND.  ALLOCATED( surf_file%usws ) )                    &
5206          surf_target%usws(m_target) = surf_file%usws(m_file)
5207    ENDIF
5208
5209    IF ( INDEX( restart_string(1:length), '%vsws' ) /= 0 )  THEN
5210       IF ( ALLOCATED( surf_target%vsws )  .AND.  ALLOCATED( surf_file%vsws ) )                    &
5211          surf_target%vsws(m_target) = surf_file%vsws(m_file)
5212    ENDIF
5213
5214    IF ( INDEX( restart_string(1:length), '%ts' ) /= 0 )  THEN
5215       IF ( ALLOCATED( surf_target%ts )  .AND.  ALLOCATED( surf_file%ts ) )                        &
5216          surf_target%ts(m_target) = surf_file%ts(m_file)
5217    ENDIF
5218
5219    IF ( INDEX( restart_string(1:length), '%shf' ) /= 0 )  THEN
5220       IF ( ALLOCATED( surf_target%shf )  .AND.  ALLOCATED( surf_file%shf ) )                      &
5221          surf_target%shf(m_target) = surf_file%shf(m_file)
5222    ENDIF
5223
5224    IF ( INDEX( restart_string(1:length), '%qs' ) /= 0 )  THEN
5225       IF ( ALLOCATED( surf_target%qs )  .AND.  ALLOCATED( surf_file%qs ) )                        &
5226          surf_target%qs(m_target) = surf_file%qs(m_file)
5227    ENDIF
5228
5229    IF ( INDEX( restart_string(1:length), '%qsws' ) /= 0 )  THEN
5230       IF ( ALLOCATED( surf_target%qsws )  .AND.  ALLOCATED( surf_file%qsws ) )                    &
5231          surf_target%qsws(m_target) = surf_file%qsws(m_file)
5232    ENDIF
5233
5234    IF ( INDEX( restart_string(1:length), '%ss' ) /= 0 )  THEN
5235       IF ( ALLOCATED( surf_target%ss )  .AND.  ALLOCATED( surf_file%ss ) )                        &
5236          surf_target%ss(m_target) = surf_file%ss(m_file)
5237    ENDIF
5238
5239    IF ( INDEX( restart_string(1:length), '%ssws' ) /= 0 )  THEN
5240       IF ( ALLOCATED( surf_target%ssws )  .AND.  ALLOCATED( surf_file%ssws ) )                    &
5241          surf_target%ssws(m_target) = surf_file%ssws(m_file)
5242    ENDIF
5243
5244    IF ( INDEX( restart_string(1:length), '%css' ) /= 0 )  THEN
5245       IF ( ALLOCATED( surf_target%css )  .AND.  ALLOCATED( surf_file%css ) )  THEN
5246          DO  lsp = 1, nvar
5247             surf_target%css(lsp,m_target) = surf_file%css(lsp,m_file)
5248          ENDDO
5249       ENDIF
5250    ENDIF
5251    IF ( INDEX( restart_string(1:length), '%cssws' ) /= 0 )  THEN
5252       IF ( ALLOCATED( surf_target%cssws )  .AND.  ALLOCATED( surf_file%cssws ) )  THEN
5253          DO  lsp = 1, nvar
5254             surf_target%cssws(lsp,m_target) = surf_file%cssws(lsp,m_file)
5255          ENDDO
5256       ENDIF
5257    ENDIF
5258
5259    IF ( INDEX( restart_string(1:length), '%qcs' ) /= 0 )  THEN
5260       IF ( ALLOCATED( surf_target%qcs )  .AND.  ALLOCATED( surf_file%qcs ) )                      &
5261         surf_target%qcs(m_target) = surf_file%qcs(m_file)
5262    ENDIF
5263
5264    IF ( INDEX( restart_string(1:length), '%qcsws' ) /= 0 )  THEN
5265       IF ( ALLOCATED( surf_target%qcsws )  .AND.  ALLOCATED( surf_file%qcsws ) )                  &
5266          surf_target%qcsws(m_target) = surf_file%qcsws(m_file)
5267    ENDIF
5268
5269    IF ( INDEX( restart_string(1:length), '%ncs' ) /= 0 )  THEN
5270       IF ( ALLOCATED( surf_target%ncs )  .AND.  ALLOCATED( surf_file%ncs ) )                      &
5271          surf_target%ncs(m_target) = surf_file%ncs(m_file)
5272    ENDIF
5273
5274    IF ( INDEX( restart_string(1:length), '%ncsws' ) /= 0 )  THEN
5275       IF ( ALLOCATED( surf_target%ncsws )  .AND.  ALLOCATED( surf_file%ncsws ) )                  &
5276          surf_target%ncsws(m_target) = surf_file%ncsws(m_file)
5277    ENDIF
5278
5279    IF ( INDEX( restart_string(1:length), '%qis' ) /= 0 )  THEN
5280       IF ( ALLOCATED( surf_target%qis )  .AND.  ALLOCATED( surf_file%qis ) )                      &
5281         surf_target%qis(m_target) = surf_file%qis(m_file)
5282    ENDIF
5283
5284    IF ( INDEX( restart_string(1:length), '%qisws' ) /= 0 )  THEN
5285       IF ( ALLOCATED( surf_target%qisws )  .AND.  ALLOCATED( surf_file%qisws ) )                  &
5286          surf_target%qisws(m_target) = surf_file%qisws(m_file)
5287    ENDIF
5288
5289    IF ( INDEX( restart_string(1:length), '%nis' ) /= 0 )  THEN
5290       IF ( ALLOCATED( surf_target%nis )  .AND.  ALLOCATED( surf_file%nis ) )                      &
5291          surf_target%nis(m_target) = surf_file%nis(m_file)
5292    ENDIF
5293
5294    IF ( INDEX( restart_string(1:length), '%nisws' ) /= 0 )  THEN
5295       IF ( ALLOCATED( surf_target%nisws )  .AND.  ALLOCATED( surf_file%nisws ) )                  &
5296          surf_target%nisws(m_target) = surf_file%nisws(m_file)
5297    ENDIF
5298
5299    IF ( INDEX( restart_string(1:length), '%qrs' ) /= 0 )  THEN
5300       IF ( ALLOCATED( surf_target%qrs )  .AND.  ALLOCATED( surf_file%qrs ) )                      &
5301         surf_target%qrs(m_target) = surf_file%qrs(m_file)
5302    ENDIF
5303
5304    IF ( INDEX( restart_string(1:length), '%qrsws' ) /= 0 )  THEN
5305       IF ( ALLOCATED( surf_target%qrsws )  .AND.  ALLOCATED( surf_file%qrsws ) )                  &
5306          surf_target%qrsws(m_target) = surf_file%qrsws(m_file)
5307    ENDIF
5308
5309    IF ( INDEX( restart_string(1:length), '%nrs' ) /= 0 )  THEN
5310       IF ( ALLOCATED( surf_target%nrs )  .AND.  ALLOCATED( surf_file%nrs ) )                      &
5311          surf_target%nrs(m_target) = surf_file%nrs(m_file)
5312    ENDIF
5313
5314    IF ( INDEX( restart_string(1:length), '%nrsws' ) /= 0 )  THEN
5315       IF ( ALLOCATED( surf_target%nrsws )  .AND.  ALLOCATED( surf_file%nrsws ) )                  &
5316          surf_target%nrsws(m_target) = surf_file%nrsws(m_file)
5317    ENDIF
5318
5319    IF ( INDEX( restart_string(1:length), '%sasws' ) /= 0 )  THEN
5320       IF ( ALLOCATED( surf_target%sasws )  .AND.  ALLOCATED( surf_file%sasws ) )                  &
5321          surf_target%sasws(m_target) = surf_file%sasws(m_file)
5322    ENDIF
5323
5324    IF ( INDEX( restart_string(1:length), '%mom_uv' ) /= 0 )  THEN
5325       IF ( ALLOCATED( surf_target%mom_flux_uv )  .AND.  ALLOCATED( surf_file%mom_flux_uv ) )      &
5326          surf_target%mom_flux_uv(m_target) = surf_file%mom_flux_uv(m_file)
5327    ENDIF
5328
5329    IF ( INDEX( restart_string(1:length), '%mom_w' ) /= 0 )  THEN
5330       IF ( ALLOCATED( surf_target%mom_flux_w )  .AND.  ALLOCATED( surf_file%mom_flux_w ) )        &
5331          surf_target%mom_flux_w(m_target) = surf_file%mom_flux_w(m_file)
5332    ENDIF
5333
5334    IF ( INDEX( restart_string(1:length), '%mom_tke' ) /= 0 )  THEN
5335       IF ( ALLOCATED( surf_target%mom_flux_tke )  .AND.                                           &
5336            ALLOCATED( surf_file%mom_flux_tke ) )                                                  &
5337          surf_target%mom_flux_tke(0:1,m_target) = surf_file%mom_flux_tke(0:1,m_file)
5338    ENDIF
5339
5340
5341 END SUBROUTINE restore_surface_elements
5342
5343 END SUBROUTINE surface_rrd_local_ftn
5344
5345
5346!--------------------------------------------------------------------------------------------------!
5347! Description:
5348! ------------
5349!> Reads surface-related restart data in MPI-IO format. TO_DO: this routine needs to be adjusted for
5350!> cyclic_fill mode
5351!--------------------------------------------------------------------------------------------------!
5352 SUBROUTINE surface_rrd_local_mpi
5353
5354
5355    IMPLICIT NONE
5356
5357    CHARACTER(LEN=1) ::  dum  !< dummy string to create input-variable name
5358
5359    INTEGER(iwp) ::  i  !< loop index, x-direction
5360    INTEGER(iwp) ::  j  !< loop index, y-direction
5361    INTEGER(iwp) ::  l  !< loop index for surface orientation
5362    INTEGER(iwp) ::  m  !< loop index for surface types - target array
5363    INTEGER(iwp) ::  mm !< loop index for surface types - file array
5364
5365    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index  !< index for surface data (MPI-IO)
5366
5367    LOGICAL ::  ldum            !< dummy variable
5368    LOGICAL ::  surf_match_def  !< flag indicating that surface element is of default type
5369    LOGICAL ::  surf_match_lsm  !< flag indicating that surface element is of natural type
5370    LOGICAL ::  surf_match_usm  !< flag indicating that surface element is of urban type
5371
5372    TYPE(surf_type), DIMENSION(0:2) ::  surf_h  !< gathered horizontal surfaces, contains all surface types
5373    TYPE(surf_type), DIMENSION(0:3) ::  surf_v  !< gathered vertical surfaces, contains all surface types
5374
5375!
5376!-- Get total number of surface points on the file
5377    CALL rrd_mpi_io_global_array( 'ns_h_on_file', ns_h_on_file )
5378    CALL rrd_mpi_io_global_array( 'ns_v_on_file', ns_v_on_file )
5379
5380
5381    DO  l = 0, 2
5382
5383       IF ( ns_h_on_file(l) == 0 )  CYCLE  !< No data of this surface type on file
5384
5385       IF ( ALLOCATED( surf_h(l)%start_index ) )  CALL deallocate_surface_attributes_h( surf_h(l) )
5386       surf_h(l)%ns = ns_h_on_file(l)
5387       CALL allocate_surface_attributes_h( surf_h(l), nys, nyn, nxl, nxr )
5388
5389       WRITE( dum, '(I1)') l
5390
5391       CALL rrd_mpi_io( 'surf_h(' // dum // ')%start_index',  surf_h(l)%start_index )
5392       CALL rrd_mpi_io( 'surf_h(' // dum // ')%end_index',  surf_h(l)%end_index )
5393       CALL rrd_mpi_io( 'global_start_index_h_' // dum , global_start_index )
5394
5395       CALL rd_mpi_io_surface_filetypes( surf_h(l)%start_index, surf_h(l)%end_index, ldum,         &
5396                                         global_start_index )
5397
5398       IF ( ALLOCATED ( surf_h(l)%us ) )  THEN
5399          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%us', surf_h(l)%us )
5400       ENDIF
5401
5402       IF ( ALLOCATED ( surf_h(l)%ts ) )  THEN
5403          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%ts', surf_h(l)%ts )
5404       ENDIF
5405
5406       IF ( ALLOCATED ( surf_h(l)%qs ) )  THEN
5407          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qs', surf_h(l)%qs )
5408       ENDIF
5409
5410       IF ( ALLOCATED ( surf_h(l)%ss ) )  THEN
5411          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%ss', surf_h(l)%ss )
5412       ENDIF
5413
5414       IF ( ALLOCATED ( surf_h(l)%qcs ) )  THEN
5415          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qcs', surf_h(l)%qcs )
5416       ENDIF
5417
5418       IF ( ALLOCATED ( surf_h(l)%ncs ) )  THEN
5419          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%ncs', surf_h(l)%ncs )
5420       ENDIF
5421
5422       IF ( ALLOCATED ( surf_h(l)%qis ) )  THEN
5423          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qis', surf_h(l)%qis )
5424       ENDIF
5425
5426       IF ( ALLOCATED ( surf_h(l)%nis ) )  THEN
5427          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%nis', surf_h(l)%nis )
5428       ENDIF
5429
5430       IF ( ALLOCATED ( surf_h(l)%qrs ) )  THEN
5431          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qrs', surf_h(l)%qrs )
5432       ENDIF
5433
5434       IF ( ALLOCATED ( surf_h(l)%nrs ) )  THEN
5435          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%nrs', surf_h(l)%nrs )
5436       ENDIF
5437
5438       IF ( ALLOCATED ( surf_h(l)%ol ) )  THEN
5439          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%ol', surf_h(l)%ol )
5440       ENDIF
5441
5442       IF ( ALLOCATED ( surf_h(l)%rib ) )  THEN
5443          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%rib',  surf_h(l)%rib )
5444       ENDIF
5445
5446       IF ( ALLOCATED ( surf_h(l)%pt_surface ) )  THEN
5447          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%pt_surface', surf_h(l)%pt_surface )
5448       ENDIF
5449
5450       IF ( ALLOCATED ( surf_h(l)%q_surface ) )  THEN
5451          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%q_surface', surf_h(l)%q_surface )
5452       ENDIF
5453
5454       IF ( ALLOCATED ( surf_h(l)%vpt_surface ) )  THEN
5455          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%vpt_surface', surf_h(l)%vpt_surface )
5456       ENDIF
5457
5458       IF ( ALLOCATED ( surf_h(l)%usws ) )  THEN
5459          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%usws', surf_h(l)%usws )
5460       ENDIF
5461
5462       IF ( ALLOCATED ( surf_h(l)%vsws ) )  THEN
5463          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%vsws', surf_h(l)%vsws )
5464       ENDIF
5465
5466       IF ( ALLOCATED ( surf_h(l)%shf ) )  THEN
5467          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%shf', surf_h(l)%shf )
5468       ENDIF
5469
5470       IF ( ALLOCATED ( surf_h(l)%qsws ) )  THEN
5471          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qsws', surf_h(l)%qsws )
5472       ENDIF
5473
5474       IF ( ALLOCATED ( surf_h(l)%ssws ) )  THEN
5475          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%ssws', surf_h(l)%ssws )
5476       ENDIF
5477
5478       IF ( ALLOCATED ( surf_h(l)%css ) )  THEN
5479          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%css', surf_h(l)%css )
5480       ENDIF
5481
5482       IF ( ALLOCATED ( surf_h(l)%cssws ) )  THEN
5483          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%cssws', surf_h(l)%cssws )
5484       ENDIF
5485
5486       IF ( ALLOCATED ( surf_h(l)%qcsws ) )  THEN
5487          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qcsws', surf_h(l)%qcsws )
5488       ENDIF
5489
5490       IF ( ALLOCATED ( surf_h(l)%ncsws ) )  THEN
5491          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%ncsws', surf_h(l)%ncsws )
5492       ENDIF
5493
5494       IF ( ALLOCATED ( surf_h(l)%qisws ) )  THEN
5495          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qisws', surf_h(l)%qisws )
5496       ENDIF
5497
5498       IF ( ALLOCATED ( surf_h(l)%nisws ) )  THEN
5499          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%nisws', surf_h(l)%nisws )
5500       ENDIF
5501
5502       IF ( ALLOCATED ( surf_h(l)%qrsws ) )  THEN
5503          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%qrsws', surf_h(l)%qrsws )
5504       ENDIF
5505
5506       IF ( ALLOCATED ( surf_h(l)%nrsws ) )  THEN
5507          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%nrsws', surf_h(l)%nrsws )
5508       ENDIF
5509
5510       IF ( ALLOCATED ( surf_h(l)%sasws ) )  THEN
5511          CALL rrd_mpi_io_surface( 'surf_h(' // dum // ')%sasws', surf_h(l)%sasws )
5512       ENDIF
5513
5514    ENDDO
5515
5516!
5517!-- Read vertical surfaces
5518    DO  l = 0, 3
5519
5520       IF ( ns_v_on_file(l) == 0 )  CYCLE  !< No data of this surface type on file
5521
5522       IF ( ALLOCATED( surf_v(l)%start_index ) )  CALL deallocate_surface_attributes_v( surf_v(l) )
5523       surf_v(l)%ns = ns_v_on_file(l)
5524       CALL allocate_surface_attributes_v( surf_v(l), nys, nyn, nxl, nxr )
5525
5526       WRITE( dum, '(I1)' ) l
5527
5528       CALL rrd_mpi_io( 'surf_v(' // dum // ')%start_index', surf_v(l)%start_index )
5529       CALL rrd_mpi_io( 'surf_v(' // dum // ')%end_index', surf_v(l)%end_index )
5530       CALL rrd_mpi_io( 'global_start_index_v_' // dum , global_start_index )
5531
5532       CALL rd_mpi_io_surface_filetypes( surf_v(l)%start_index, surf_v(l)%end_index, ldum,         &
5533                                         global_start_index )
5534
5535       IF ( ALLOCATED ( surf_v(l)%us ) )  THEN
5536          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%us',  surf_v(l)%us )
5537       ENDIF
5538
5539       IF ( ALLOCATED ( surf_v(l)%ts ) )  THEN
5540          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%ts', surf_v(l)%ts )
5541       ENDIF
5542
5543       IF ( ALLOCATED ( surf_v(l)%qs ) )  THEN
5544          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qs',  surf_v(l)%qs )
5545       ENDIF
5546
5547       IF ( ALLOCATED ( surf_v(l)%ss ) )  THEN
5548          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%ss',  surf_v(l)%ss )
5549       ENDIF
5550
5551       IF ( ALLOCATED ( surf_v(l)%qcs ) )  THEN
5552          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qcs', surf_v(l)%qcs )
5553       ENDIF
5554
5555       IF ( ALLOCATED ( surf_v(l)%ncs ) )  THEN
5556          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%ncs', surf_v(l)%ncs )
5557       ENDIF
5558
5559       IF ( ALLOCATED ( surf_v(l)%qis ) )  THEN
5560          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qis', surf_v(l)%qis )
5561       ENDIF
5562
5563       IF ( ALLOCATED ( surf_v(l)%nis ) )  THEN
5564          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%nis', surf_v(l)%nis )
5565       ENDIF
5566
5567       IF ( ALLOCATED ( surf_v(l)%qrs ) )  THEN
5568          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qrs', surf_v(l)%qrs )
5569       ENDIF
5570
5571       IF ( ALLOCATED ( surf_v(l)%nrs ) )  THEN
5572          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%nrs', surf_v(l)%nrs )
5573       ENDIF
5574
5575       IF ( ALLOCATED ( surf_v(l)%ol ) )  THEN
5576          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%ol', surf_v(l)%ol )
5577       ENDIF
5578
5579       IF ( ALLOCATED ( surf_v(l)%rib ) )  THEN
5580          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%rib', surf_v(l)%rib )
5581       ENDIF
5582
5583       IF ( ALLOCATED ( surf_v(l)%pt_surface ) )  THEN
5584          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%pt_surface', surf_v(l)%pt_surface )
5585       ENDIF
5586
5587       IF ( ALLOCATED ( surf_v(l)%q_surface ) )  THEN
5588          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%q_surface', surf_v(l)%q_surface )
5589       ENDIF
5590
5591       IF ( ALLOCATED ( surf_v(l)%vpt_surface ) )  THEN
5592          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%vpt_surface', surf_v(l)%vpt_surface )
5593       ENDIF
5594
5595       IF ( ALLOCATED ( surf_v(l)%shf ) )  THEN
5596          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%shf', surf_v(l)%shf )
5597       ENDIF
5598
5599       IF ( ALLOCATED ( surf_v(l)%qsws ) )  THEN
5600          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qsws', surf_v(l)%qsws )
5601       ENDIF
5602
5603       IF ( ALLOCATED ( surf_v(l)%ssws ) )  THEN
5604          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%ssws', surf_v(l)%ssws )
5605       ENDIF
5606
5607       IF ( ALLOCATED ( surf_v(l)%css ) )  THEN
5608          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%css', surf_v(l)%css )
5609       ENDIF
5610
5611       IF ( ALLOCATED ( surf_v(l)%cssws ) )  THEN
5612          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%cssws', surf_v(l)%cssws )
5613       ENDIF
5614
5615       IF ( ALLOCATED ( surf_v(l)%qcsws ) )  THEN
5616          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qcsws', surf_v(l)%qcsws )
5617       ENDIF
5618
5619       IF ( ALLOCATED ( surf_v(l)%ncsws ) )  THEN
5620          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%ncsws', surf_v(l)%ncsws )
5621       ENDIF
5622
5623       IF ( ALLOCATED ( surf_v(l)%qisws ) )  THEN
5624          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qisws', surf_v(l)%qisws )
5625       ENDIF
5626
5627       IF ( ALLOCATED ( surf_v(l)%nisws ) )  THEN
5628          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%nisws', surf_v(l)%nisws )
5629       ENDIF
5630
5631       IF ( ALLOCATED ( surf_v(l)%qrsws ) )  THEN
5632          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%qrsws', surf_v(l)%qrsws )
5633       ENDIF
5634
5635       IF ( ALLOCATED ( surf_v(l)%nrsws ) )  THEN
5636          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%nrsws', surf_v(l)%nrsws )
5637       ENDIF
5638
5639       IF ( ALLOCATED ( surf_v(l)%sasws ) )  THEN
5640          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%sasws', surf_v(l)%sasws )
5641       ENDIF
5642
5643       IF ( ALLOCATED ( surf_v(l)%mom_flux_uv ) )  THEN
5644          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%mom_uv', surf_v(l)%mom_flux_uv )
5645       ENDIF
5646
5647       IF ( ALLOCATED ( surf_v(l)%mom_flux_w ) )  THEN
5648          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%mom_w',  surf_v(l)%mom_flux_w )
5649       ENDIF
5650
5651       IF ( ALLOCATED ( surf_v(l)%mom_flux_tke ) )  THEN
5652          CALL rrd_mpi_io_surface( 'surf_v(' // dum // ')%mom_tke', surf_v(l)%mom_flux_tke )
5653       ENDIF
5654
5655    ENDDO
5656
5657!
5658!-- Redistribute surface elements on its respective type. Start with horizontal default surfaces.
5659    DO  l = 0, 2
5660       DO  i = nxl, nxr
5661          DO  j = nys, nyn
5662             surf_match_def  = surf_def_h(l)%end_index(j,i) >= surf_def_h(l)%start_index(j,i)
5663             IF ( l < 2 )  THEN
5664                surf_match_lsm  = surf_lsm_h(l)%end_index(j,i) >= surf_lsm_h(l)%start_index(j,i)
5665                surf_match_usm  = surf_usm_h(l)%end_index(j,i) >= surf_usm_h(l)%start_index(j,i)
5666             ELSE
5667                surf_match_lsm  = .FALSE.
5668                surf_match_usm  = .FALSE.
5669             ENDIF
5670             IF ( surf_match_def )  THEN
5671!
5672!--             Set the start index for the local surface element
5673                mm = surf_def_h(l)%start_index(j,i)
5674!
5675!--             For index pair (j,i) on file loop from start to end index, and in case the local
5676!--             surface element mm is smaller than the local end index, assign the respective
5677!--             surface data to this element.
5678                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
5679                   IF ( surf_def_h(l)%end_index(j,i) >= mm )                                       &
5680                      CALL restore_surface_elements( surf_def_h(l), mm, surf_h(l), m )
5681                   mm = mm + 1
5682                ENDDO
5683             ENDIF
5684!--          Natural- and urban-like horizontal surfaces.
5685             IF ( surf_match_lsm )  THEN
5686                mm = surf_lsm_h(l)%start_index(j,i)
5687                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
5688                   IF ( surf_lsm_h(l)%end_index(j,i) >= mm )                                             &
5689                      CALL restore_surface_elements( surf_lsm_h(l), mm, surf_h(l), m )
5690                   mm = mm + 1
5691                ENDDO
5692             ENDIF
5693             IF ( surf_match_usm )  THEN
5694                mm = surf_usm_h(l)%start_index(j,i)
5695                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
5696                   IF ( surf_usm_h(l)%end_index(j,i) >= mm )                                             &
5697                      CALL restore_surface_elements( surf_usm_h(l), mm, surf_h(l), m )
5698                   mm = mm + 1
5699                ENDDO
5700             ENDIF
5701          ENDDO
5702       ENDDO
5703    ENDDO
5704!
5705!-- Same for vertical surfaces.
5706    DO  l = 0, 3
5707       DO  i = nxl, nxr
5708          DO  j = nys, nyn
5709             surf_match_def  = surf_def_v(l)%end_index(j,i) >= surf_def_v(l)%start_index(j,i)
5710             surf_match_lsm  = surf_lsm_v(l)%end_index(j,i) >= surf_lsm_v(l)%start_index(j,i)
5711             surf_match_usm  = surf_usm_v(l)%end_index(j,i) >= surf_usm_v(l)%start_index(j,i)
5712
5713             IF ( surf_match_def )  THEN
5714                mm = surf_def_v(l)%start_index(j,i)
5715                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
5716                   IF ( surf_def_v(l)%end_index(j,i) >= mm )                                       &
5717                      CALL restore_surface_elements( surf_def_v(l), mm, surf_v(l), m )
5718                   mm = mm + 1
5719                ENDDO
5720             ENDIF
5721             IF ( surf_match_lsm )  THEN
5722                mm = surf_lsm_v(l)%start_index(j,i)
5723                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
5724                   IF ( surf_lsm_v(l)%end_index(j,i) >= mm )                                       &
5725                      CALL restore_surface_elements( surf_lsm_v(l), mm, surf_v(l), m )
5726                   mm = mm + 1
5727                ENDDO
5728             ENDIF
5729             IF ( surf_match_usm )  THEN
5730                mm = surf_usm_v(l)%start_index(j,i)
5731                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
5732                   IF ( surf_usm_v(l)%end_index(j,i) >= mm )                                       &
5733                      CALL restore_surface_elements( surf_usm_v(l), mm, surf_v(l), m )
5734                   mm = mm + 1
5735                ENDDO
5736             ENDIF
5737          ENDDO
5738       ENDDO
5739    ENDDO
5740
5741 CONTAINS
5742
5743!--------------------------------------------------------------------------------------------------!
5744! Description:
5745! ------------
5746!> Restores surface elements back on its respective type.
5747!--------------------------------------------------------------------------------------------------!
5748 SUBROUTINE restore_surface_elements( surf_target, m_target, surf_file, m_file )
5749
5750    INTEGER(iwp) ::  m_file    !< respective surface-element index of current surface array
5751    INTEGER(iwp) ::  m_target  !< respecitve surface-element index of surface array on file
5752    INTEGER(iwp) ::  lsp       !< running index chemical species
5753
5754    TYPE(surf_type) ::  surf_target  !< target surface type
5755    TYPE(surf_type) ::  surf_file    !< surface type on file
5756
5757    IF ( ALLOCATED( surf_target%us )  .AND.  ALLOCATED( surf_file%us ) )                           &
5758       surf_target%us(m_target) = surf_file%us(m_file)
5759
5760    IF ( ALLOCATED( surf_target%ol )  .AND.  ALLOCATED( surf_file%ol ) )                           &
5761       surf_target%ol(m_target) = surf_file%ol(m_file)
5762
5763    IF ( ALLOCATED( surf_target%rib )  .AND.  ALLOCATED( surf_file%rib ) )                         &
5764       surf_target%rib(m_target) = surf_file%rib(m_file)
5765
5766    IF ( ALLOCATED( surf_target%ol )  .AND.  ALLOCATED( surf_file%ol ) )                           &
5767       surf_target%ol(m_target) = surf_file%ol(m_file)
5768
5769    IF ( ALLOCATED( surf_target%pt_surface )  .AND.  ALLOCATED( surf_file%pt_surface ) )           &
5770       surf_target%pt_surface(m_target) = surf_file%pt_surface(m_file)
5771
5772    IF ( ALLOCATED( surf_target%q_surface )  .AND.  ALLOCATED( surf_file%q_surface ) )             &
5773       surf_target%q_surface(m_target) = surf_file%q_surface(m_file)
5774
5775    IF ( ALLOCATED( surf_target%vpt_surface )  .AND.  ALLOCATED( surf_file%vpt_surface ) )         &
5776       surf_target%vpt_surface(m_target) = surf_file%vpt_surface(m_file)
5777
5778    IF ( ALLOCATED( surf_target%usws )  .AND.  ALLOCATED( surf_file%usws ) )                       &
5779       surf_target%usws(m_target) = surf_file%usws(m_file)
5780
5781    IF ( ALLOCATED( surf_target%vsws )  .AND.  ALLOCATED( surf_file%vsws ) )                       &
5782       surf_target%vsws(m_target) = surf_file%vsws(m_file)
5783
5784    IF ( ALLOCATED( surf_target%ts )  .AND.  ALLOCATED( surf_file%ts ) )                           &
5785       surf_target%ts(m_target) = surf_file%ts(m_file)
5786
5787    IF ( ALLOCATED( surf_target%shf )  .AND.  ALLOCATED( surf_file%shf ) )                         &
5788       surf_target%shf(m_target) = surf_file%shf(m_file)
5789
5790    IF ( ALLOCATED( surf_target%qs )  .AND.  ALLOCATED( surf_file%qs ) )                           &
5791       surf_target%qs(m_target) = surf_file%qs(m_file)
5792
5793    IF ( ALLOCATED( surf_target%qsws )  .AND.  ALLOCATED( surf_file%qsws ) )                       &
5794       surf_target%qsws(m_target) = surf_file%qsws(m_file)
5795
5796    IF ( ALLOCATED( surf_target%ss )  .AND.  ALLOCATED( surf_file%ss ) )                           &
5797       surf_target%ss(m_target) = surf_file%ss(m_file)
5798
5799    IF ( ALLOCATED( surf_target%ssws )  .AND.  ALLOCATED( surf_file%ssws ) )                       &
5800       surf_target%ssws(m_target) = surf_file%ssws(m_file)
5801
5802    IF ( ALLOCATED( surf_target%css )  .AND.  ALLOCATED( surf_file%css ) )  THEN
5803       DO  lsp = 1, nvar
5804          surf_target%css(lsp,m_target) = surf_file%css(lsp,m_file)
5805       ENDDO
5806    ENDIF
5807
5808    IF ( ALLOCATED( surf_target%cssws )  .AND.  ALLOCATED( surf_file%cssws ) )  THEN
5809       DO  lsp = 1, nvar
5810          surf_target%cssws(lsp,m_target) = surf_file%cssws(lsp,m_file)
5811       ENDDO
5812    ENDIF
5813
5814    IF ( ALLOCATED( surf_target%qcs )  .AND.  ALLOCATED( surf_file%qcs ) )                         &
5815      surf_target%qcs(m_target) = surf_file%qcs(m_file)
5816
5817    IF ( ALLOCATED( surf_target%qcsws )  .AND.  ALLOCATED( surf_file%qcsws ) )                     &
5818       surf_target%qcsws(m_target) = surf_file%qcsws(m_file)
5819
5820    IF ( ALLOCATED( surf_target%ncs )  .AND.  ALLOCATED( surf_file%ncs ) )                         &
5821       surf_target%ncs(m_target) = surf_file%ncs(m_file)
5822
5823    IF ( ALLOCATED( surf_target%ncsws )  .AND.  ALLOCATED( surf_file%ncsws ) )                     &
5824       surf_target%ncsws(m_target) = surf_file%ncsws(m_file)
5825
5826    IF ( ALLOCATED( surf_target%qis )  .AND.  ALLOCATED( surf_file%qis ) )                         &
5827      surf_target%qis(m_target) = surf_file%qis(m_file)
5828
5829    IF ( ALLOCATED( surf_target%qisws )  .AND.  ALLOCATED( surf_file%qisws ) )                     &
5830       surf_target%qisws(m_target) = surf_file%qisws(m_file)
5831
5832    IF ( ALLOCATED( surf_target%nis )  .AND.  ALLOCATED( surf_file%nis ) )                         &
5833       surf_target%nis(m_target) = surf_file%nis(m_file)
5834
5835    IF ( ALLOCATED( surf_target%nisws )  .AND.  ALLOCATED( surf_file%nisws ) )                     &
5836       surf_target%nisws(m_target) = surf_file%nisws(m_file)
5837
5838    IF ( ALLOCATED( surf_target%qrs )  .AND.  ALLOCATED( surf_file%qrs ) )                         &
5839       surf_target%qrs(m_target) = surf_file%qrs(m_file)
5840
5841    IF ( ALLOCATED( surf_target%qrsws )  .AND.  ALLOCATED( surf_file%qrsws ) )                     &
5842       surf_target%qrsws(m_target) = surf_file%qrsws(m_file)
5843
5844    IF ( ALLOCATED( surf_target%nrs )  .AND.  ALLOCATED( surf_file%nrs ) )                         &
5845       surf_target%nrs(m_target) = surf_file%nrs(m_file)
5846
5847    IF ( ALLOCATED( surf_target%nrsws )  .AND.  ALLOCATED( surf_file%nrsws ) )                     &
5848       surf_target%nrsws(m_target) = surf_file%nrsws(m_file)
5849
5850    IF ( ALLOCATED( surf_target%sasws )  .AND.  ALLOCATED( surf_file%sasws ) )                     &
5851       surf_target%sasws(m_target) = surf_file%sasws(m_file)
5852
5853    IF ( ALLOCATED( surf_target%mom_flux_uv )  .AND.  ALLOCATED( surf_file%mom_flux_uv ) )         &
5854       surf_target%mom_flux_uv(m_target) = surf_file%mom_flux_uv(m_file)
5855
5856    IF ( ALLOCATED( surf_target%mom_flux_w )  .AND.  ALLOCATED( surf_file%mom_flux_w ) )           &
5857       surf_target%mom_flux_w(m_target) = surf_file%mom_flux_w(m_file)
5858
5859    IF ( ALLOCATED( surf_target%mom_flux_tke )  .AND.                                              &
5860         ALLOCATED( surf_file%mom_flux_tke   ) )                                                   &
5861       surf_target%mom_flux_tke(0:1,m_target) = surf_file%mom_flux_tke(0:1,m_file)
5862
5863 END SUBROUTINE restore_surface_elements
5864
5865 END SUBROUTINE surface_rrd_local_mpi
5866
5867!--------------------------------------------------------------------------------------------------!
5868! Description:
5869! ------------
5870!> Counts the number of surface elements with the same facing, required for reading and writing
5871!> restart data.
5872!--------------------------------------------------------------------------------------------------!
5873 SUBROUTINE surface_last_actions
5874
5875    IMPLICIT NONE
5876!
5877!-- Horizontal surfaces
5878    ns_h_on_file(0) = surf_def_h(0)%ns + surf_lsm_h(0)%ns + surf_usm_h(0)%ns
5879    ns_h_on_file(1) = surf_def_h(1)%ns + surf_lsm_h(1)%ns + surf_usm_h(1)%ns
5880    ns_h_on_file(2) = surf_def_h(2)%ns
5881!
5882!-- Vertical surfaces
5883    ns_v_on_file(0) = surf_def_v(0)%ns + surf_lsm_v(0)%ns + surf_usm_v(0)%ns
5884    ns_v_on_file(1) = surf_def_v(1)%ns + surf_lsm_v(1)%ns + surf_usm_v(1)%ns
5885    ns_v_on_file(2) = surf_def_v(2)%ns + surf_lsm_v(2)%ns + surf_usm_v(2)%ns
5886    ns_v_on_file(3) = surf_def_v(3)%ns + surf_lsm_v(3)%ns + surf_usm_v(3)%ns
5887
5888 END SUBROUTINE surface_last_actions
5889
5890!--------------------------------------------------------------------------------------------------!
5891! Description:
5892! ------------
5893!> Routine maps surface data read from file after restart - 1D arrays.
5894!--------------------------------------------------------------------------------------------------!
5895 SUBROUTINE surface_restore_elements_1d( surf_target, surf_file, start_index_c,                    &
5896                                         start_index_on_file, end_index_on_file, nxlc, nysc, nxlf, &
5897                                         nxrf, nysf, nynf, nys_on_file, nyn_on_file, nxl_on_file,  &
5898                                         nxr_on_file )
5899
5900    IMPLICIT NONE
5901
5902    INTEGER(iwp) ::  i     !< running index along x-direction, refers to former domain size
5903    INTEGER(iwp) ::  ic    !< running index along x-direction, refers to current domain size
5904    INTEGER(iwp) ::  j     !< running index along y-direction, refers to former domain size
5905    INTEGER(iwp) ::  jc    !< running index along y-direction, refers to former domain size
5906    INTEGER(iwp) ::  m     !< surface-element index on file
5907    INTEGER(iwp) ::  mm    !< surface-element index on current subdomain
5908    INTEGER(iwp) ::  nxlc  !< index of left boundary on current subdomain
5909    INTEGER(iwp) ::  nxlf  !< index of left boundary on former subdomain
5910    INTEGER(iwp) ::  nxrf  !< index of right boundary on former subdomain
5911    INTEGER(iwp) ::  nysc  !< index of north boundary on current subdomain
5912    INTEGER(iwp) ::  nynf  !< index of north boundary on former subdomain
5913    INTEGER(iwp) ::  nysf  !< index of south boundary on former subdomain
5914
5915    INTEGER(iwp) ::  nxl_on_file  !< leftmost index on file
5916    INTEGER(iwp) ::  nxr_on_file  !< rightmost index on file
5917    INTEGER(iwp) ::  nyn_on_file  !< northmost index on file
5918    INTEGER(iwp) ::  nys_on_file  !< southmost index on file
5919
5920    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  start_index_c  !<
5921    INTEGER(iwp), DIMENSION(nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) ::  start_index_on_file  !< start index of surface
5922                                                                                                      !< elements on file
5923    INTEGER(iwp), DIMENSION(nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) ::  end_index_on_file    !< end index of surface
5924                                                                                                      !< elements on file
5925
5926    REAL(wp), DIMENSION(:) ::  surf_target  !< target surface type
5927    REAL(wp), DIMENSION(:) ::  surf_file    !< surface type on file
5928
5929    ic = nxlc
5930    DO  i = nxlf, nxrf
5931       jc = nysc
5932       DO  j = nysf, nynf
5933          mm = start_index_c(jc,ic)
5934          DO  m = start_index_on_file(j,i), end_index_on_file(j,i)
5935             surf_target(mm) = surf_file(m)
5936             mm = mm + 1
5937          ENDDO
5938          jc = jc + 1
5939       ENDDO
5940       ic = ic + 1
5941    ENDDO
5942
5943
5944 END SUBROUTINE surface_restore_elements_1d
5945
5946!--------------------------------------------------------------------------------------------------!
5947! Description:
5948! ------------
5949!> Routine maps surface data read from file after restart - 2D arrays
5950!--------------------------------------------------------------------------------------------------!
5951 SUBROUTINE surface_restore_elements_2d( surf_target, surf_file, start_index_c,                    &
5952                                         start_index_on_file, end_index_on_file, nxlc, nysc, nxlf, &
5953                                         nxrf, nysf, nynf, nys_on_file, nyn_on_file, nxl_on_file,  &
5954                                         nxr_on_file )
5955
5956    IMPLICIT NONE
5957
5958    INTEGER(iwp) ::  i     !< running index along x-direction, refers to former domain size
5959    INTEGER(iwp) ::  ic    !< running index along x-direction, refers to current domain size
5960    INTEGER(iwp) ::  j     !< running index along y-direction, refers to former domain size
5961    INTEGER(iwp) ::  jc    !< running index along y-direction, refers to former domain size
5962    INTEGER(iwp) ::  m     !< surface-element index on file
5963    INTEGER(iwp) ::  mm    !< surface-element index on current subdomain
5964    INTEGER(iwp) ::  nxlc  !< index of left boundary on current subdomain
5965    INTEGER(iwp) ::  nxlf  !< index of left boundary on former subdomain
5966    INTEGER(iwp) ::  nxrf  !< index of right boundary on former subdomain
5967    INTEGER(iwp) ::  nysc  !< index of north boundary on current subdomain
5968    INTEGER(iwp) ::  nynf  !< index of north boundary on former subdomain
5969    INTEGER(iwp) ::  nysf  !< index of south boundary on former subdomain
5970
5971    INTEGER(iwp) ::  nxl_on_file  !< leftmost index on file
5972    INTEGER(iwp) ::  nxr_on_file  !< rightmost index on file
5973    INTEGER(iwp) ::  nyn_on_file  !< northmost index on file
5974    INTEGER(iwp) ::  nys_on_file  !< southmost index on file
5975
5976    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  start_index_c !< start index of surface type
5977
5978    INTEGER(iwp), DIMENSION(nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) ::  start_index_on_file  !< start index of surface
5979                                                                                                      !< elements on file
5980    INTEGER(iwp), DIMENSION(nys_on_file:nyn_on_file,nxl_on_file:nxr_on_file) ::  end_index_on_file    !< end index of surface
5981                                                                                                      !< elements on file
5982
5983    REAL(wp), DIMENSION(:,:) ::  surf_target !< target surface type
5984    REAL(wp), DIMENSION(:,:) ::  surf_file   !< surface type on file
5985
5986    ic = nxlc
5987    DO  i = nxlf, nxrf
5988       jc = nysc
5989       DO  j = nysf, nynf
5990          mm = start_index_c(jc,ic)
5991          DO  m = start_index_on_file(j,i), end_index_on_file(j,i)
5992             surf_target(:,mm) = surf_file(:,m)
5993             mm = mm + 1
5994          ENDDO
5995          jc = jc + 1
5996       ENDDO
5997       ic = ic + 1
5998    ENDDO
5999
6000 END SUBROUTINE surface_restore_elements_2d
6001
6002
6003 END MODULE surface_mod
Note: See TracBrowser for help on using the repository browser.