source: palm/trunk/SOURCE/netcdf_data_input_mod.f90 @ 3294

Last change on this file since 3294 was 3257, checked in by suehring, 6 years ago

Further adjustment of checks for building_type and building_id (required as type and id can be modified by the topography filtering)

  • Property svn:keywords set to Id
File size: 225.0 KB
Line 
1!> @file netcdf_data_input_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
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2018 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: netcdf_data_input_mod.f90 3257 2018-09-17 17:11:46Z raasch $
27! Adjust checks for building_type and building_id, which is necessary after
28! topography filtering (building_type and id can be modified by the filtering).
29!
30! 3254 2018-09-17 10:53:57Z suehring
31! Additional check for surface_fractions and and checks for building_id and
32! building_type extended.
33!
34! 3241 2018-09-12 15:02:00Z raasch
35! unused variables removed
36!
37! 3215 2018-08-29 09:58:59Z suehring
38! - Separate input of soil properties from input of atmospheric data. This
39!   enables input of soil properties also in child domains without any
40!   dependence on atmospheric input
41! - Check for missing initial 1D/3D data in dynamic input file
42! - Revise checks for matching grid spacing in model and input file
43! - Bugfix, add netcdf4_parallel directive for collective read operation
44! - Revise error message numbers
45!
46! 3209 2018-08-27 16:58:37Z suehring
47! Read zsoil dimension length only if soil variables are provided
48!
49! 3183 2018-07-27 14:25:55Z suehring
50! Adjust input of dynamic driver according to revised Inifor version.
51! Replace simulated_time by time_since_reference_point.
52! Rename variables in mesoscale-offline nesting mode.
53!
54! 3182 2018-07-27 13:36:03Z suehring
55! Slightly revise check for surface_fraction in order to check only the relevant
56! fractions
57!
58! 3103 2018-07-04 17:30:52Z suehring
59! New check for negative terrain heights
60!
61! 3089 2018-06-27 13:20:38Z suehring
62! Revise call for message routine in case of local data inconsistencies.
63!
64! 3054 2018-06-01 16:08:59Z gronemeier
65! Bugfix: force an MPI abort if errors occur while reading building heights
66! from ASCII file
67!
68! 3053 2018-06-01 12:59:07Z suehring
69! Revise checks for variable surface_fraction
70!
71! 3051 2018-05-30 17:43:55Z suehring
72! - Speed-up NetCDF input
73! - Revise input routines and remove NetCDF input via IO-blocks since this is
74!   not working in parallel mode in case blocking collective read operations
75!   are done
76! - Temporarily revoke renaming of input variables in dynamic driver (tend_ug,
77!   tend_vg, zsoil) in order to keep dynamic input file working with current
78!   model version
79! - More detailed error messages created
80!
81! 3045 2018-05-28 07:55:41Z Giersch
82! Error messages revised
83!
84! 3041 2018-05-25 10:39:54Z gronemeier
85! Add data type for global file attributes
86! Add read of global attributes of static driver
87!
88! 3037 2018-05-24 10:39:29Z gronemeier
89! renamed 'depth' to 'zsoil'
90!
91! 3036 2018-05-24 10:18:26Z gronemeier
92! Revision of input vars according to UC2 data standard
93!  - renamed 'orography_2D' to 'zt'
94!  - renamed 'buildings_2D' to 'buildings_2d'
95!  - renamed 'buildings_3D' to 'buildings_3d'
96!  - renamed 'leaf_are_density' to 'lad'
97!  - renamed 'basal_are_density' to 'bad'
98!  - renamed 'root_are_density_lad' to 'root_area_dens_r'
99!  - renamed 'root_are_density_lsm' to 'root_area_dens_s'
100!  - renamed 'ls_forcing_ug' to 'tend_ug'
101!  - renamed 'ls_forcing_vg' to 'tend_vg'
102!
103! 3019 2018-05-13 07:05:43Z maronga
104! Improved reading speed of large NetCDF files
105!
106! 2963 2018-04-12 14:47:44Z suehring
107! - Revise checks for static input variables.
108! - Introduce index for vegetation/wall, pavement/green-wall and water/window
109!   surfaces, for clearer access of surface fraction, albedo, emissivity, etc. .
110!
111! 2958 2018-04-11 15:38:13Z suehring
112! Synchronize longitude and latitude between nested model domains, values are
113! taken from the root model.
114!
115! 2955 2018-04-09 15:14:01Z suehring
116! Extend checks for consistent setting of buildings, its ID and type.
117! Add log-points to measure CPU time of NetCDF data input.
118!
119! 2953 2018-04-09 11:26:02Z suehring
120! Bugfix in checks for initialization data
121!
122! 2947 2018-04-04 18:01:41Z suehring
123! Checks for dynamic input revised
124!
125! 2946 2018-04-04 17:01:23Z suehring
126! Bugfix for revision 2945, perform checks only if dynamic input file is
127! available.
128!
129! 2945 2018-04-04 16:27:14Z suehring
130! - Mimic for topography input slightly revised, in order to enable consistency
131!   checks
132! - Add checks for dimensions in dynamic input file and move already existing
133!   checks
134!
135! 2938 2018-03-27 15:52:42Z suehring
136! Initial read of geostrophic wind components from dynamic driver.
137!
138! 2773 2018-01-30 14:12:54Z suehring
139! Revise checks for surface_fraction.
140!
141! 2925 2018-03-23 14:54:11Z suehring
142! Check for further inconsistent settings of surface_fractions.
143! Some messages slightly rephrased and error numbers renamed.
144!
145! 2898 2018-03-15 13:03:01Z suehring
146! Check if each building has a type. Further, check if dimensions in static
147! input file match the model dimensions.
148!
149! 2897 2018-03-15 11:47:16Z suehring
150! Relax restrictions for topography input, terrain and building heights can be
151! input separately and are not mandatory any more.
152!
153! 2874 2018-03-13 10:55:42Z knoop
154! Bugfix: wrong placement of netcdf cpp-macros fixed
155!
156! 2794 2018-02-07 14:09:43Z knoop
157! Check if 3D building input is consistent to numeric grid.
158!
159! 2773 2018-01-30 14:12:54Z suehring
160! - Enable initialization with 3D topography.
161! - Move check for correct initialization in nesting mode to check_parameters.
162!
163! 2772 2018-01-29 13:10:35Z suehring
164! Initialization of simulation independent on land-surface model.
165!
166! 2746 2018-01-15 12:06:04Z suehring
167! Read plant-canopy variables independently on land-surface model usage
168!
169! 2718 2018-01-02 08:49:38Z maronga
170! Corrected "Former revisions" section
171!
172! 2711 2017-12-20 17:04:49Z suehring
173! Rename subroutine close_file to avoid double-naming.
174!
175! 2700 2017-12-15 14:12:35Z suehring
176!
177! 2696 2017-12-14 17:12:51Z kanani
178! Initial revision (suehring)
179!
180!
181!
182!
183! Authors:
184! --------
185! @author Matthias Suehring
186!
187! Description:
188! ------------
189!> Modulue contains routines to input data according to Palm input data
190!> standart using dynamic and static input files.
191!>
192!> @todo - Order input alphabetically
193!> @todo - Revise error messages and error numbers
194!> @todo - Input of missing quantities (chemical species, emission rates)
195!> @todo - Defninition and input of still missing variable attributes
196!> @todo - Input of initial geostrophic wind profiles with cyclic conditions.
197!------------------------------------------------------------------------------!
198 MODULE netcdf_data_input_mod
199
200    USE control_parameters,                                                    &
201        ONLY:  coupling_char, io_blocks, io_group
202
203    USE cpulog,                                                                &
204        ONLY:  cpu_log, log_point_s
205
206    USE kinds
207
208#if defined ( __netcdf )
209    USE NETCDF
210#endif
211
212    USE pegrid
213
214    USE surface_mod,                                                           &
215        ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win
216!
217!-- Define type for dimensions.
218    TYPE dims_xy
219       INTEGER(iwp) :: nx                             !< dimension length in x
220       INTEGER(iwp) :: ny                             !< dimension length in y
221       INTEGER(iwp) :: nz                             !< dimension length in z
222       REAL(wp), DIMENSION(:), ALLOCATABLE :: x       !< dimension array in x
223       REAL(wp), DIMENSION(:), ALLOCATABLE :: y       !< dimension array in y
224       REAL(wp), DIMENSION(:), ALLOCATABLE :: z       !< dimension array in z
225    END TYPE dims_xy
226!
227!-- Define data type for nesting in larger-scale models like COSMO.
228!-- Data type comprises u, v, w, pt, and q at lateral and top boundaries.
229    TYPE nest_offl_type
230
231       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
232
233       INTEGER(iwp) ::  nt     !< number of time levels in dynamic input file
234       INTEGER(iwp) ::  nzu    !< number of vertical levels on scalar grid in dynamic input file
235       INTEGER(iwp) ::  nzw    !< number of vertical levels on w grid in dynamic input file
236       INTEGER(iwp) ::  tind   !< time index for reference time in mesoscale-offline nesting
237       INTEGER(iwp) ::  tind_p !< time index for following time in mesoscale-offline nesting
238
239       LOGICAL      ::  init         = .FALSE.
240       LOGICAL      ::  from_file    = .FALSE.
241
242       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surface_pressure !< time dependent surface pressure
243       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time             !< time levels in dynamic input file
244       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos         !< vertical levels at scalar grid in dynamic input file
245       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw_atmos         !< vertical levels at w grid in dynamic input file
246
247       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ug         !< domain-averaged geostrophic component
248       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vg         !< domain-averaged geostrophic component
249
250       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_left   !< u-component at left boundary
251       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_left   !< v-component at left boundary
252       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_left   !< w-component at left boundary
253       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_left   !< mixing ratio at left boundary
254       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_left  !< potentital temperautre at left boundary
255
256       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_north  !< u-component at north boundary
257       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_north  !< v-component at north boundary
258       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_north  !< w-component at north boundary
259       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_north  !< mixing ratio at north boundary
260       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_north !< potentital temperautre at north boundary
261
262       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_right  !< u-component at right boundary
263       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_right  !< v-component at right boundary
264       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_right  !< w-component at right boundary
265       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_right  !< mixing ratio at right boundary
266       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_right !< potentital temperautre at right boundary
267
268       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_south  !< u-component at south boundary
269       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_south  !< v-component at south boundary
270       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_south  !< w-component at south boundary
271       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_south  !< mixing ratio at south boundary
272       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_south !< potentital temperautre at south boundary
273
274       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_top    !< u-component at top boundary
275       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_top    !< v-component at top boundary
276       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_top    !< w-component at top boundary
277       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_top    !< mixing ratio at top boundary
278       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
279
280    END TYPE nest_offl_type
281
282    TYPE init_type
283
284       CHARACTER(LEN=23) ::  origin_time !< reference time of input data
285
286       INTEGER(iwp) ::  lod_msoil !< level of detail - soil moisture
287       INTEGER(iwp) ::  lod_pt    !< level of detail - pt
288       INTEGER(iwp) ::  lod_q     !< level of detail - q
289       INTEGER(iwp) ::  lod_tsoil !< level of detail - soil temperature
290       INTEGER(iwp) ::  lod_u     !< level of detail - u-component
291       INTEGER(iwp) ::  lod_v     !< level of detail - v-component
292       INTEGER(iwp) ::  lod_w     !< level of detail - w-component
293       INTEGER(iwp) ::  nx        !< number of scalar grid points along x in dynamic input file
294       INTEGER(iwp) ::  nxu       !< number of u grid points along x in dynamic input file
295       INTEGER(iwp) ::  ny        !< number of scalar grid points along y in dynamic input file
296       INTEGER(iwp) ::  nyv       !< number of v grid points along y in dynamic input file
297       INTEGER(iwp) ::  nzs       !< number of vertical soil levels in dynamic input file
298       INTEGER(iwp) ::  nzu       !< number of vertical levels on scalar grid in dynamic input file
299       INTEGER(iwp) ::  nzw       !< number of vertical levels on w grid in dynamic input file
300
301       LOGICAL ::  from_file_msoil  = .FALSE. !< flag indicating whether soil moisture is already initialized from file
302       LOGICAL ::  from_file_pt     = .FALSE. !< flag indicating whether pt is already initialized from file
303       LOGICAL ::  from_file_q      = .FALSE. !< flag indicating whether q is already initialized from file
304       LOGICAL ::  from_file_tsoil  = .FALSE. !< flag indicating whether soil temperature is already initialized from file
305       LOGICAL ::  from_file_u      = .FALSE. !< flag indicating whether u is already initialized from file
306       LOGICAL ::  from_file_ug     = .FALSE. !< flag indicating whether ug is already initialized from file
307       LOGICAL ::  from_file_v      = .FALSE. !< flag indicating whether v is already initialized from file
308       LOGICAL ::  from_file_vg     = .FALSE. !< flag indicating whether ug is already initialized from file
309       LOGICAL ::  from_file_w      = .FALSE. !< flag indicating whether w is already initialized from file
310
311       REAL(wp) ::  fill_msoil       !< fill value for soil moisture
312       REAL(wp) ::  fill_pt          !< fill value for pt
313       REAL(wp) ::  fill_q           !< fill value for q
314       REAL(wp) ::  fill_tsoil       !< fill value for soil temperature
315       REAL(wp) ::  fill_u           !< fill value for u
316       REAL(wp) ::  fill_v           !< fill value for v
317       REAL(wp) ::  fill_w           !< fill value for w
318       REAL(wp) ::  latitude         !< latitude of the southern model boundary
319       REAL(wp) ::  longitude        !< longitude of the western model boundary
320       REAL(wp) ::  origin_x         !< x position of the western model boundary
321       REAL(wp) ::  origin_y         !< y position of the northern model boundary
322       REAL(wp) ::  origin_z         !< reference height of input data
323       REAL(wp) ::  rotation_angle   !< rotation angle of input data
324
325       REAL(wp), DIMENSION(:), ALLOCATABLE ::  msoil_1d     !< initial vertical profile of soil moisture
326       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init      !< initial vertical profile of pt
327       REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init       !< initial vertical profile of q
328       REAL(wp), DIMENSION(:), ALLOCATABLE ::  tsoil_1d     !< initial vertical profile of soil temperature
329       REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_init       !< initial vertical profile of u
330       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ug_init      !< initial vertical profile of ug
331       REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_init       !< initial vertical profile of v
332       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vg_init      !< initial vertical profile of ug
333       REAL(wp), DIMENSION(:), ALLOCATABLE ::  w_init       !< initial vertical profile of w
334       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z_soil       !< vertical levels in soil in dynamic input file, used for interpolation
335       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos     !< vertical levels at scalar grid in dynamic input file, used for interpolation
336       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw_atmos     !< vertical levels at w grid in dynamic input file, used for interpolation
337
338
339       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  msoil_3d !< initial 3d soil moisture provide by Inifor and interpolated onto soil grid
340       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tsoil_3d !< initial 3d soil temperature provide by Inifor and interpolated onto soil grid
341
342    END TYPE init_type
343
344!
345!-- Define data structures for different input data types.
346!-- 8-bit Integer 2D
347    TYPE int_2d_8bit
348       INTEGER(KIND=1) ::  fill = -127                      !< fill value
349       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE ::  var !< respective variable
350
351       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
352    END TYPE int_2d_8bit
353!
354!-- 32-bit Integer 2D
355    TYPE int_2d_32bit
356       INTEGER(iwp) ::  fill = -9999                      !< fill value
357       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  var  !< respective variable
358
359       LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used
360    END TYPE int_2d_32bit
361
362!
363!-- Define data type to read 2D real variables
364    TYPE real_2d
365       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
366
367       REAL(wp) ::  fill = -9999.9_wp                !< fill value
368       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var !< respective variable
369    END TYPE real_2d
370
371!
372!-- Define data type to read 2D real variables
373    TYPE real_3d
374       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
375
376       INTEGER(iwp) ::  nz   !< number of grid points along vertical dimension
377
378       REAL(wp) ::  fill = -9999.9_wp                  !< fill value
379       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  var !< respective variable
380    END TYPE real_3d
381!
382!-- Define data structure where the dimension and type of the input depends
383!-- on the given level of detail.
384!-- For buildings, the input is either 2D float, or 3d byte.
385    TYPE build_in
386       INTEGER(iwp)    ::  lod = 1                               !< level of detail
387       INTEGER(KIND=1) ::  fill2 = -127                          !< fill value for lod = 2
388       INTEGER(iwp)    ::  nz                                    !< number of vertical layers in file
389       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d !< 3d variable (lod = 2)
390
391       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z                 !< vertical coordinate for 3D building, used for consistency check
392
393       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
394
395       REAL(wp)                              ::  fill1 = -9999.9_wp !< fill values for lod = 1
396       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var_2d             !< 2d variable (lod = 1)
397    END TYPE build_in
398
399!
400!-- For soil_type, the input is either 2D or 3D one-byte integer.
401    TYPE soil_in
402       INTEGER(iwp)                                   ::  lod = 1      !< level of detail
403       INTEGER(KIND=1)                                ::  fill = -127  !< fill value for lod = 2
404       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE   ::  var_2d       !< 2d variable (lod = 1)
405       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d       !< 3d variable (lod = 2)
406
407       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
408    END TYPE soil_in
409
410!
411!-- Define data type for fractions between surface types
412    TYPE fracs
413       INTEGER(iwp)                            ::  nf             !< total number of fractions
414       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nfracs         !< dimension array for fraction
415
416       LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used
417
418       REAL(wp)                                ::  fill = -9999.9_wp !< fill value
419       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  frac              !< respective fraction between different surface types
420    END TYPE fracs
421!
422!-- Data type for parameter lists, Depending on the given level of detail,
423!-- the input is 3D or 4D
424    TYPE pars
425       INTEGER(iwp)                            ::  lod = 1         !< level of detail
426       INTEGER(iwp)                            ::  np              !< total number of parameters
427       INTEGER(iwp)                            ::  nz              !< vertical dimension - number of soil layers
428       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  layers          !< dimension array for soil layers
429       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  pars            !< dimension array for parameters
430
431       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
432
433       REAL(wp)                                  ::  fill = -9999.9_wp !< fill value
434       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  pars_xy           !< respective parameters, level of detail = 1
435       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  pars_xyz          !< respective parameters, level of detail = 2
436    END TYPE pars
437!
438!-- Define type for global file attributes
439!-- Please refer to the PALM data standard for a detailed description of each
440!-- attribute.
441    TYPE global_atts_type
442       CHARACTER(LEN=12 ) ::  acronym                            !< acronym of institution
443       CHARACTER(LEN=7)   ::  acronym_char = 'acronym'           !< name of attribute
444       CHARACTER(LEN=200) ::  author                             !< first name, last name, email adress
445       CHARACTER(LEN=6)   ::  author_char = 'author'             !< name of attribute
446       CHARACTER(LEN=12 ) ::  campaign                           !< name of campaign
447       CHARACTER(LEN=8)   ::  campaign_char = 'campaign'         !< name of attribute
448       CHARACTER(LEN=200) ::  comment                            !< comment to data
449       CHARACTER(LEN=7)   ::  comment_char = 'comment'           !< name of attribute
450       CHARACTER(LEN=200) ::  contact_person                     !< first name, last name, email adress
451       CHARACTER(LEN=14)  ::  contact_person_char = 'contact_person'  !< name of attribute
452       CHARACTER(LEN=200) ::  conventions = 'CF-1.7'             !< netCDF convention
453       CHARACTER(LEN=11)  ::  conventions_char = 'Conventions'   !< name of attribute
454       CHARACTER(LEN=23 ) ::  creation_time                      !< creation time of data set
455       CHARACTER(LEN=13)  ::  creation_time_char = 'creation_time'  !< name of attribute
456       CHARACTER(LEN=16 ) ::  data_content                       !< content of data set
457       CHARACTER(LEN=12)  ::  data_content_char = 'data_content' !< name of attribute
458       CHARACTER(LEN=200) ::  dependencies                       !< dependencies of data set
459       CHARACTER(LEN=12)  ::  dependencies_char = 'dependencies' !< name of attribute
460       CHARACTER(LEN=200) ::  history                            !< information about data processing
461       CHARACTER(LEN=7)   ::  history_char = 'history'           !< name of attribute
462       CHARACTER(LEN=200) ::  institution                        !< name of responsible institution
463       CHARACTER(LEN=11)  ::  institution_char = 'institution'   !< name of attribute
464       CHARACTER(LEN=200) ::  keywords                           !< keywords of data set
465       CHARACTER(LEN=8)   ::  keywords_char = 'keywords'         !< name of attribute
466       CHARACTER(LEN=200) ::  license                            !< license of data set
467       CHARACTER(LEN=7)   ::  license_char = 'license'           !< name of attribute
468       CHARACTER(LEN=200) ::  location                           !< place which refers to data set
469       CHARACTER(LEN=8)   ::  location_char = 'location'         !< name of attribute
470       CHARACTER(LEN=10)  ::  origin_lat_char = 'origin_lat'     !< name of attribute
471       CHARACTER(LEN=10)  ::  origin_lon_char = 'origin_lon'     !< name of attribute
472       CHARACTER(LEN=23 ) ::  origin_time                        !< reference time
473       CHARACTER(LEN=11)  ::  origin_time_char = 'origin_time'   !< name of attribute
474       CHARACTER(LEN=8)   ::  origin_x_char = 'origin_x'         !< name of attribute
475       CHARACTER(LEN=8)   ::  origin_y_char = 'origin_y'         !< name of attribute
476       CHARACTER(LEN=8)   ::  origin_z_char = 'origin_z'         !< name of attribute
477       CHARACTER(LEN=12)  ::  palm_version_char = 'palm_version' !< name of attribute
478       CHARACTER(LEN=200) ::  references                         !< literature referring to data set
479       CHARACTER(LEN=10)  ::  references_char = 'references'     !< name of attribute
480       CHARACTER(LEN=14)  ::  rotation_angle_char = 'rotation_angle'  !< name of attribute
481       CHARACTER(LEN=12 ) ::  site                               !< name of model domain
482       CHARACTER(LEN=4)   ::  site_char = 'site'                 !< name of attribute
483       CHARACTER(LEN=200) ::  source                             !< source of data set
484       CHARACTER(LEN=6)   ::  source_char = 'source'             !< name of attribute
485       CHARACTER(LEN=200) ::  title                              !< title of data set
486       CHARACTER(LEN=5)   ::  title_char = 'title'               !< name of attribute
487       CHARACTER(LEN=7)   ::  version_char = 'version'           !< name of attribute
488
489       INTEGER(iwp) ::  version              !< version of data set
490
491       REAL(wp) ::  origin_lat               !< latitude of lower left corner
492       REAL(wp) ::  origin_lon               !< longitude of lower left corner
493       REAL(wp) ::  origin_x                 !< easting (UTM coordinate) of lower left corner
494       REAL(wp) ::  origin_y                 !< northing (UTM coordinate) of lower left corner
495       REAL(wp) ::  origin_z                 !< reference height
496       REAL(wp) ::  palm_version             !< PALM version of data set
497       REAL(wp) ::  rotation_angle           !< rotation angle of coordinate system of data set
498    END TYPE global_atts_type
499!
500!-- Define variables
501    TYPE(dims_xy)    ::  dim_static  !< data structure for x, y-dimension in static input file
502
503    TYPE(nest_offl_type) ::  nest_offl  !< data structure for data input at lateral and top boundaries (provided by Inifor) 
504
505    TYPE(init_type) ::  init_3d    !< data structure for the initialization of the 3D flow and soil fields
506    TYPE(init_type) ::  init_model !< data structure for the initialization of the model
507
508!
509!-- Define 2D variables of type NC_BYTE
510    TYPE(int_2d_8bit)  ::  albedo_type_f     !< input variable for albedo type
511    TYPE(int_2d_8bit)  ::  building_type_f   !< input variable for building type
512    TYPE(int_2d_8bit)  ::  pavement_type_f   !< input variable for pavenment type
513    TYPE(int_2d_8bit)  ::  street_crossing_f !< input variable for water type
514    TYPE(int_2d_8bit)  ::  street_type_f     !< input variable for water type
515    TYPE(int_2d_8bit)  ::  vegetation_type_f !< input variable for vegetation type
516    TYPE(int_2d_8bit)  ::  water_type_f      !< input variable for water type
517
518!
519!-- Define 2D variables of type NC_INT
520    TYPE(int_2d_32bit) ::  building_id_f     !< input variable for building ID
521!
522!-- Define 2D variables of type NC_FLOAT
523    TYPE(real_2d) ::  terrain_height_f       !< input variable for terrain height
524!
525!-- Define 3D variables of type NC_FLOAT
526    TYPE(real_3d) ::  basal_area_density_f    !< input variable for basal area density - resolved vegetation
527    TYPE(real_3d) ::  leaf_area_density_f     !< input variable for leaf area density - resolved vegetation
528    TYPE(real_3d) ::  root_area_density_lad_f !< input variable for root area density - resolved vegetation
529    TYPE(real_3d) ::  root_area_density_lsm_f !< input variable for root area density - parametrized vegetation
530
531!
532!-- Define input variable for buildings
533    TYPE(build_in) ::  buildings_f           !< input variable for buildings
534!
535!-- Define input variables for soil_type
536    TYPE(soil_in)  ::  soil_type_f           !< input variable for soil type
537
538    TYPE(fracs) ::  surface_fraction_f       !< input variable for surface fraction
539
540    TYPE(pars)  ::  albedo_pars_f              !< input variable for albedo parameters
541    TYPE(pars)  ::  building_pars_f            !< input variable for building parameters
542    TYPE(pars)  ::  pavement_pars_f            !< input variable for pavement parameters
543    TYPE(pars)  ::  pavement_subsurface_pars_f !< input variable for pavement parameters
544    TYPE(pars)  ::  soil_pars_f                !< input variable for soil parameters
545    TYPE(pars)  ::  vegetation_pars_f          !< input variable for vegetation parameters
546    TYPE(pars)  ::  water_pars_f               !< input variable for water parameters
547
548
549    CHARACTER(LEN=3)  ::  char_lod  = 'lod'         !< name of level-of-detail attribute in NetCDF file
550
551    CHARACTER(LEN=10) ::  char_fill = '_FillValue'        !< name of fill value attribute in NetCDF file
552
553    CHARACTER(LEN=100) ::  input_file_static  = 'PIDS_STATIC'  !< Name of file which comprises static input data
554    CHARACTER(LEN=100) ::  input_file_dynamic = 'PIDS_DYNAMIC' !< Name of file which comprises dynamic input data
555
556    INTEGER(iwp) ::  nc_stat         !< return value of nf90 function call
557
558    LOGICAL ::  input_pids_static  = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing static information exists
559    LOGICAL ::  input_pids_dynamic = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing dynamic information exists
560
561    LOGICAL ::  collective_read = .FALSE.      !< Enable NetCDF collective read
562
563    TYPE(global_atts_type) ::  input_file_atts !< global attributes of input file
564
565    SAVE
566
567    PRIVATE
568
569    INTERFACE netcdf_data_input_interpolate
570       MODULE PROCEDURE netcdf_data_input_interpolate_1d
571       MODULE PROCEDURE netcdf_data_input_interpolate_1d_soil
572       MODULE PROCEDURE netcdf_data_input_interpolate_2d
573       MODULE PROCEDURE netcdf_data_input_interpolate_3d
574    END INTERFACE netcdf_data_input_interpolate
575
576    INTERFACE netcdf_data_input_check_dynamic
577       MODULE PROCEDURE netcdf_data_input_check_dynamic
578    END INTERFACE netcdf_data_input_check_dynamic
579
580    INTERFACE netcdf_data_input_check_static
581       MODULE PROCEDURE netcdf_data_input_check_static
582    END INTERFACE netcdf_data_input_check_static
583
584    INTERFACE netcdf_data_input_inquire_file
585       MODULE PROCEDURE netcdf_data_input_inquire_file
586    END INTERFACE netcdf_data_input_inquire_file
587
588    INTERFACE netcdf_data_input_init
589       MODULE PROCEDURE netcdf_data_input_init
590    END INTERFACE netcdf_data_input_init
591
592    INTERFACE netcdf_data_input_init_3d
593       MODULE PROCEDURE netcdf_data_input_init_3d
594    END INTERFACE netcdf_data_input_init_3d
595   
596    INTERFACE netcdf_data_input_init_lsm
597       MODULE PROCEDURE netcdf_data_input_init_lsm
598    END INTERFACE netcdf_data_input_init_lsm
599
600    INTERFACE netcdf_data_input_lsf
601       MODULE PROCEDURE netcdf_data_input_lsf
602    END INTERFACE netcdf_data_input_lsf
603
604    INTERFACE netcdf_data_input_surface_data
605       MODULE PROCEDURE netcdf_data_input_surface_data
606    END INTERFACE netcdf_data_input_surface_data
607
608    INTERFACE netcdf_data_input_topo
609       MODULE PROCEDURE netcdf_data_input_topo
610    END INTERFACE netcdf_data_input_topo
611
612    INTERFACE get_variable
613       MODULE PROCEDURE get_variable_1d_int
614       MODULE PROCEDURE get_variable_1d_real
615       MODULE PROCEDURE get_variable_2d_int8
616       MODULE PROCEDURE get_variable_2d_int32
617       MODULE PROCEDURE get_variable_2d_real
618       MODULE PROCEDURE get_variable_3d_int8
619       MODULE PROCEDURE get_variable_3d_real
620       MODULE PROCEDURE get_variable_3d_real_dynamic
621       MODULE PROCEDURE get_variable_4d_real
622    END INTERFACE get_variable
623
624    INTERFACE get_variable_pr
625       MODULE PROCEDURE get_variable_pr
626    END INTERFACE get_variable_pr
627
628    INTERFACE get_attribute
629       MODULE PROCEDURE get_attribute_real
630       MODULE PROCEDURE get_attribute_int8
631       MODULE PROCEDURE get_attribute_int32
632       MODULE PROCEDURE get_attribute_string
633    END INTERFACE get_attribute
634
635!
636!-- Public variables
637    PUBLIC albedo_pars_f, albedo_type_f, basal_area_density_f, buildings_f,    &
638           building_id_f, building_pars_f, building_type_f, init_3d,           &
639           init_model, input_file_static, input_pids_static,                   &
640           input_pids_dynamic, leaf_area_density_f, nest_offl,                 &
641           pavement_pars_f, pavement_subsurface_pars_f, pavement_type_f,       &
642           root_area_density_lad_f, root_area_density_lsm_f, soil_pars_f,      &
643           soil_type_f, street_crossing_f, street_type_f, surface_fraction_f,  &
644           terrain_height_f, vegetation_pars_f, vegetation_type_f,             &
645           water_pars_f, water_type_f
646
647!
648!-- Public subroutines
649    PUBLIC netcdf_data_input_check_dynamic, netcdf_data_input_check_static,    &
650           netcdf_data_input_inquire_file,                                     &
651           netcdf_data_input_init, netcdf_data_input_init_lsm,                 &
652           netcdf_data_input_init_3d,                                          &
653           netcdf_data_input_interpolate, netcdf_data_input_lsf,               &
654           netcdf_data_input_surface_data, netcdf_data_input_topo
655
656 CONTAINS
657
658!------------------------------------------------------------------------------!
659! Description:
660! ------------
661!> Inquires whether NetCDF input files according to Palm-input-data standard
662!> exist. Moreover, basic checks are performed.
663!------------------------------------------------------------------------------!
664    SUBROUTINE netcdf_data_input_inquire_file
665
666       USE control_parameters,                                                 &
667           ONLY:  topo_no_distinct
668
669       IMPLICIT NONE
670
671#if defined ( __netcdf )
672       INQUIRE( FILE = TRIM( input_file_static ) // TRIM( coupling_char ),     &
673                EXIST = input_pids_static  )
674       INQUIRE( FILE = TRIM( input_file_dynamic ) // TRIM( coupling_char ),    &
675                EXIST = input_pids_dynamic )
676#endif
677
678!
679!--    As long as topography can be input via ASCII format, no distinction
680!--    between building and terrain can be made. This case, classify all
681!--    surfaces as default type. Same in case land-surface and urban-surface
682!--    model are not applied.
683       IF ( .NOT. input_pids_static )  THEN
684          topo_no_distinct = .TRUE.
685       ENDIF
686
687    END SUBROUTINE netcdf_data_input_inquire_file
688
689!------------------------------------------------------------------------------!
690! Description:
691! ------------
692!> Reads global attributes required for initialization of the model.
693!------------------------------------------------------------------------------!
694    SUBROUTINE netcdf_data_input_init
695
696       IMPLICIT NONE
697
698       INTEGER(iwp) ::  id_mod   !< NetCDF id of input file
699
700       IF ( .NOT. input_pids_static )  RETURN
701
702#if defined ( __netcdf )
703!
704!--    Open file in read-only mode
705       CALL open_read_file( TRIM( input_file_static ) //                       &
706                            TRIM( coupling_char ), id_mod )
707!
708!--    Read global attributes
709       CALL get_attribute( id_mod, input_file_atts%origin_lat_char,            &
710                           input_file_atts%origin_lat, .TRUE. )
711
712       CALL get_attribute( id_mod, input_file_atts%origin_lon_char,            &
713                           input_file_atts%origin_lon, .TRUE. )
714
715       CALL get_attribute( id_mod, input_file_atts%origin_time_char,           &
716                           input_file_atts%origin_time, .TRUE. )
717
718       CALL get_attribute( id_mod, input_file_atts%origin_x_char,              &
719                           input_file_atts%origin_x, .TRUE. )
720
721       CALL get_attribute( id_mod, input_file_atts%origin_y_char,              &
722                           input_file_atts%origin_y, .TRUE. )
723
724       CALL get_attribute( id_mod, input_file_atts%origin_z_char,              &
725                           input_file_atts%origin_z, .TRUE. )
726
727       CALL get_attribute( id_mod, input_file_atts%rotation_angle_char,        &
728                           input_file_atts%rotation_angle, .TRUE. )
729
730!
731!--    Finally, close input file
732       CALL close_input_file( id_mod )
733#endif
734!
735!--    Copy latitude, longitude, origin_z, rotation angle on init type
736       init_model%latitude        = input_file_atts%origin_lat
737       init_model%longitude       = input_file_atts%origin_lon
738       init_model%origin_time     = input_file_atts%origin_time 
739       init_model%origin_x        = input_file_atts%origin_x
740       init_model%origin_y        = input_file_atts%origin_y
741       init_model%origin_z        = input_file_atts%origin_z 
742       init_model%rotation_angle  = input_file_atts%rotation_angle 
743           
744!
745!--    In case of nested runs, each model domain might have different longitude
746!--    and latitude, which would result in different Coriolis parameters and
747!--    sun-zenith angles. To avoid this, longitude and latitude in each model
748!--    domain will be set to the values of the root model. Please note, this
749!--    synchronization is required already here.
750#if defined( __parallel )
751       CALL MPI_BCAST( init_model%latitude,  1, MPI_REAL, 0,                   &
752                       MPI_COMM_WORLD, ierr )
753       CALL MPI_BCAST( init_model%longitude, 1, MPI_REAL, 0,                   &
754                       MPI_COMM_WORLD, ierr )
755#endif
756
757    END SUBROUTINE netcdf_data_input_init
758
759!------------------------------------------------------------------------------!
760! Description:
761! ------------
762!> Reads surface classification data, such as vegetation and soil type, etc. .
763!------------------------------------------------------------------------------!
764    SUBROUTINE netcdf_data_input_surface_data
765
766       USE control_parameters,                                                 &
767           ONLY:  bc_lr_cyc, bc_ns_cyc, land_surface, plant_canopy,            &
768                  urban_surface
769
770       USE indices,                                                            &
771           ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg
772
773
774       IMPLICIT NONE
775
776       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names in static input file
777
778       INTEGER(iwp) ::  id_surf   !< NetCDF id of input file
779       INTEGER(iwp) ::  k         !< running index along z-direction
780       INTEGER(iwp) ::  k2        !< running index
781       INTEGER(iwp) ::  num_vars  !< number of variables in input file
782       INTEGER(iwp) ::  nz_soil   !< number of soil layers in file
783
784       INTEGER(iwp), DIMENSION(nysg:nyng,nxlg:nxrg) ::  var_exchange_int !< dummy variables used to exchange 32-bit Integer arrays
785       INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE  ::  var_dum_int_3d !< dummy variables used to exchange real arrays
786
787       REAL(wp), DIMENSION(nysg:nyng,nxlg:nxrg) ::  var_exchange_real !< dummy variables used to exchange real arrays
788
789       REAL(wp), DIMENSION(:,:,:),   ALLOCATABLE ::  var_dum_real_3d !< dummy variables used to exchange real arrays
790       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  var_dum_real_4d !< dummy variables used to exchange real arrays
791
792!
793!--    If not static input file is available, skip this routine
794       IF ( .NOT. input_pids_static )  RETURN
795!
796!--    Measure CPU time
797       CALL cpu_log( log_point_s(82), 'NetCDF input', 'start' )
798!
799!--    Read plant canopy variables.
800       IF ( plant_canopy )  THEN
801#if defined ( __netcdf )
802!
803!--       Open file in read-only mode
804          CALL open_read_file( TRIM( input_file_static ) //                    &
805                               TRIM( coupling_char ) , id_surf )
806!
807!--       At first, inquire all variable names.
808!--       This will be used to check whether an optional input variable
809!--       exist or not.
810          CALL inquire_num_variables( id_surf, num_vars )
811
812          ALLOCATE( var_names(1:num_vars) )
813          CALL inquire_variable_names( id_surf, var_names )
814
815!
816!--       Read leaf area density - resolved vegetation
817          IF ( check_existence( var_names, 'lad' ) )  THEN
818             leaf_area_density_f%from_file = .TRUE.
819             CALL get_attribute( id_surf, char_fill,                           &
820                                 leaf_area_density_f%fill,                     &
821                                 .FALSE., 'lad' )
822!
823!--          Inquire number of vertical vegetation layer
824             CALL get_dimension_length( id_surf, leaf_area_density_f%nz,       &
825                                        'zlad' )
826!
827!--          Allocate variable for leaf-area density
828             ALLOCATE( leaf_area_density_f%var( 0:leaf_area_density_f%nz-1,    &
829                                                nys:nyn,nxl:nxr) )
830
831             CALL get_variable( id_surf, 'lad', leaf_area_density_f%var,       &
832                                nxl, nxr, nys, nyn,                            &
833                                0, leaf_area_density_f%nz-1 )
834
835          ELSE
836             leaf_area_density_f%from_file = .FALSE.
837          ENDIF
838
839!
840!--       Read basal area density - resolved vegetation
841          IF ( check_existence( var_names, 'bad' ) )  THEN
842             basal_area_density_f%from_file = .TRUE.
843             CALL get_attribute( id_surf, char_fill,                           &
844                                 basal_area_density_f%fill,                    &
845                                 .FALSE., 'bad' )
846!
847!--          Inquire number of vertical vegetation layer
848             CALL get_dimension_length( id_surf, basal_area_density_f%nz,      &
849                                        'zlad' )
850!
851!--          Allocate variable
852             ALLOCATE( basal_area_density_f%var(0:basal_area_density_f%nz-1,   &
853                                                nys:nyn,nxl:nxr) )
854
855             CALL get_variable( id_surf, 'bad', basal_area_density_f%var,      &
856                                nxl, nxr, nys, nyn,                            &
857                                0,  basal_area_density_f%nz-1 )
858          ELSE
859             basal_area_density_f%from_file = .FALSE.
860          ENDIF
861
862!
863!--       Read root area density - resolved vegetation
864          IF ( check_existence( var_names, 'root_area_dens_r' ) )  THEN
865             root_area_density_lad_f%from_file = .TRUE.
866             CALL get_attribute( id_surf, char_fill,                           &
867                                 root_area_density_lad_f%fill,                 &
868                                 .FALSE., 'root_area_dens_r' )
869!
870!--          Inquire number of vertical soil layers
871             CALL get_dimension_length( id_surf,                               &
872                                        root_area_density_lad_f%nz,            &
873                                        'zsoil' )
874!
875!--          Allocate variable
876             ALLOCATE( root_area_density_lad_f%var                             &
877                                         (0:root_area_density_lad_f%nz-1,      &
878                                          nys:nyn,nxl:nxr) )
879
880             CALL get_variable( id_surf, 'root_area_dens_r',                   &
881                                root_area_density_lad_f%var,                   &
882                                nxl, nxr, nys, nyn,                            &
883                                0,  root_area_density_lad_f%nz-1 )
884          ELSE
885             root_area_density_lad_f%from_file = .FALSE.
886          ENDIF
887!
888!--       Finally, close input file
889          CALL close_input_file( id_surf )
890#endif
891       ENDIF
892!
893!--    Deallocate variable list. Will be re-allocated in case further
894!--    variables are read from file.
895       IF ( ALLOCATED( var_names ) )  DEALLOCATE( var_names )
896!
897!--    Skip the following if no land-surface or urban-surface module are
898!--    applied. This case, no one of the following variables is used anyway.
899       IF (  .NOT. land_surface  .OR.  .NOT. urban_surface )  RETURN
900!
901!--    Initialize dummy arrays used for ghost-point exchange
902       var_exchange_int  = 0
903       var_exchange_real = 0.0_wp
904
905#if defined ( __netcdf )
906!
907!--    Open file in read-only mode
908       CALL open_read_file( TRIM( input_file_static ) //                       &
909                            TRIM( coupling_char ) , id_surf )
910!
911!--    Inquire all variable names.
912!--    This will be used to check whether an optional input variable exist
913!--    or not.
914       CALL inquire_num_variables( id_surf, num_vars )
915
916       ALLOCATE( var_names(1:num_vars) )
917       CALL inquire_variable_names( id_surf, var_names )
918!
919!--    Read vegetation type and required attributes
920       IF ( check_existence( var_names, 'vegetation_type' ) )  THEN
921          vegetation_type_f%from_file = .TRUE.
922          CALL get_attribute( id_surf, char_fill,                              &
923                              vegetation_type_f%fill,                          &
924                              .FALSE., 'vegetation_type' )
925
926          ALLOCATE ( vegetation_type_f%var(nys:nyn,nxl:nxr)  )
927
928          CALL get_variable( id_surf, 'vegetation_type',                       &
929                             vegetation_type_f%var, nxl, nxr, nys, nyn )
930       ELSE
931          vegetation_type_f%from_file = .FALSE.
932       ENDIF
933
934!
935!--    Read soil type and required attributes
936       IF ( check_existence( var_names, 'soil_type' ) )  THEN
937             soil_type_f%from_file = .TRUE.
938!
939!--       Note, lod is currently not on file; skip for the moment
940!           CALL get_attribute( id_surf, char_lod,                       &
941!                                      soil_type_f%lod,                  &
942!                                      .FALSE., 'soil_type' )
943          CALL get_attribute( id_surf, char_fill,                              &
944                              soil_type_f%fill,                                &
945                              .FALSE., 'soil_type' )
946
947          IF ( soil_type_f%lod == 1 )  THEN
948
949             ALLOCATE ( soil_type_f%var_2d(nys:nyn,nxl:nxr)  )
950
951             CALL get_variable( id_surf, 'soil_type', soil_type_f%var_2d,      &
952                                nxl, nxr, nys, nyn )
953
954          ELSEIF ( soil_type_f%lod == 2 )  THEN
955!
956!--          Obtain number of soil layers from file.
957             CALL get_dimension_length( id_surf, nz_soil, 'zsoil' )
958
959             ALLOCATE ( soil_type_f%var_3d(0:nz_soil,nys:nyn,nxl:nxr) )
960
961             CALL get_variable( id_surf, 'soil_type', soil_type_f%var_3d,      &
962                                nxl, nxr, nys, nyn, 0, nz_soil )
963 
964          ENDIF
965       ELSE
966          soil_type_f%from_file = .FALSE.
967       ENDIF
968
969!
970!--    Read pavement type and required attributes
971       IF ( check_existence( var_names, 'pavement_type' ) )  THEN
972          pavement_type_f%from_file = .TRUE.
973          CALL get_attribute( id_surf, char_fill,                              &
974                              pavement_type_f%fill, .FALSE.,                   &
975                              'pavement_type' )
976
977          ALLOCATE ( pavement_type_f%var(nys:nyn,nxl:nxr)  )
978
979          CALL get_variable( id_surf, 'pavement_type', pavement_type_f%var,    &
980                             nxl, nxr, nys, nyn )
981       ELSE
982          pavement_type_f%from_file = .FALSE.
983       ENDIF
984
985!
986!--    Read water type and required attributes
987       IF ( check_existence( var_names, 'water_type' ) )  THEN
988          water_type_f%from_file = .TRUE.
989          CALL get_attribute( id_surf, char_fill, water_type_f%fill,           &
990                              .FALSE., 'water_type' )
991
992          ALLOCATE ( water_type_f%var(nys:nyn,nxl:nxr)  )
993
994          CALL get_variable( id_surf, 'water_type', water_type_f%var,          &
995                             nxl, nxr, nys, nyn )
996
997       ELSE
998          water_type_f%from_file = .FALSE.
999       ENDIF
1000!
1001!--    Read relative surface fractions of vegetation, pavement and water.
1002       IF ( check_existence( var_names, 'surface_fraction' ) )  THEN
1003          surface_fraction_f%from_file = .TRUE.
1004          CALL get_attribute( id_surf, char_fill,                              &
1005                              surface_fraction_f%fill,                         &
1006                              .FALSE., 'surface_fraction' )
1007!
1008!--       Inquire number of surface fractions
1009          CALL get_dimension_length( id_surf,                                  &
1010                                     surface_fraction_f%nf,                    &
1011                                     'nsurface_fraction' )
1012!
1013!--       Allocate dimension array and input array for surface fractions
1014          ALLOCATE( surface_fraction_f%nfracs(0:surface_fraction_f%nf-1) )
1015          ALLOCATE( surface_fraction_f%frac(0:surface_fraction_f%nf-1,         &
1016                                            nys:nyn,nxl:nxr) )
1017!
1018!--       Get dimension of surface fractions
1019          CALL get_variable( id_surf, 'nsurface_fraction',                     &
1020                             surface_fraction_f%nfracs )
1021!
1022!--       Read surface fractions
1023          CALL get_variable( id_surf, 'surface_fraction',                      &
1024                             surface_fraction_f%frac, nxl, nxr, nys, nyn,      &
1025                             0, surface_fraction_f%nf-1 )
1026       ELSE
1027          surface_fraction_f%from_file = .FALSE.
1028       ENDIF
1029!
1030!--    Read building parameters and related information
1031       IF ( check_existence( var_names, 'building_pars' ) )  THEN
1032          building_pars_f%from_file = .TRUE.
1033          CALL get_attribute( id_surf, char_fill,                              &
1034                              building_pars_f%fill,                            &
1035                              .FALSE., 'building_pars' )
1036!
1037!--       Inquire number of building parameters
1038          CALL get_dimension_length( id_surf,                                  &
1039                                     building_pars_f%np,                       &
1040                                     'nbuilding_pars' )
1041!
1042!--       Allocate dimension array and input array for building parameters
1043          ALLOCATE( building_pars_f%pars(0:building_pars_f%np-1) )
1044          ALLOCATE( building_pars_f%pars_xy(0:building_pars_f%np-1,            &
1045                                            nys:nyn,nxl:nxr) )
1046!
1047!--       Get dimension of building parameters
1048          CALL get_variable( id_surf, 'nbuilding_pars',                        &
1049                             building_pars_f%pars )
1050!
1051!--       Read building_pars
1052          CALL get_variable( id_surf, 'building_pars',                         &
1053                             building_pars_f%pars_xy, nxl, nxr, nys, nyn,      &
1054                             0, building_pars_f%np-1 )
1055       ELSE
1056          building_pars_f%from_file = .FALSE.
1057       ENDIF
1058
1059!
1060!--    Read albedo type and required attributes
1061       IF ( check_existence( var_names, 'albedo_type' ) )  THEN
1062          albedo_type_f%from_file = .TRUE.
1063          CALL get_attribute( id_surf, char_fill, albedo_type_f%fill,          &
1064                              .FALSE.,  'albedo_type' )
1065
1066          ALLOCATE ( albedo_type_f%var(nys:nyn,nxl:nxr)  )
1067         
1068          CALL get_variable( id_surf, 'albedo_type', albedo_type_f%var,        &
1069                             nxl, nxr, nys, nyn )
1070       ELSE
1071          albedo_type_f%from_file = .FALSE.
1072       ENDIF
1073!
1074!--    Read albedo parameters and related information
1075       IF ( check_existence( var_names, 'albedo_pars' ) )  THEN
1076          albedo_pars_f%from_file = .TRUE.
1077          CALL get_attribute( id_surf, char_fill, albedo_pars_f%fill,          &
1078                              .FALSE., 'albedo_pars' )
1079!
1080!--       Inquire number of albedo parameters
1081          CALL get_dimension_length( id_surf, albedo_pars_f%np,                &
1082                                     'nalbedo_pars' )
1083!
1084!--       Allocate dimension array and input array for albedo parameters
1085          ALLOCATE( albedo_pars_f%pars(0:albedo_pars_f%np-1) )
1086          ALLOCATE( albedo_pars_f%pars_xy(0:albedo_pars_f%np-1,                &
1087                                          nys:nyn,nxl:nxr) )
1088!
1089!--       Get dimension of albedo parameters
1090          CALL get_variable( id_surf, 'nalbedo_pars', albedo_pars_f%pars )
1091
1092          CALL get_variable( id_surf, 'albedo_pars', albedo_pars_f%pars_xy,    &
1093                             nxl, nxr, nys, nyn,                               &
1094                             0, albedo_pars_f%np-1 )
1095       ELSE
1096          albedo_pars_f%from_file = .FALSE.
1097       ENDIF
1098
1099!
1100!--    Read pavement parameters and related information
1101       IF ( check_existence( var_names, 'pavement_pars' ) )  THEN
1102          pavement_pars_f%from_file = .TRUE.
1103          CALL get_attribute( id_surf, char_fill,                              &
1104                              pavement_pars_f%fill,                            &
1105                              .FALSE., 'pavement_pars' )
1106!
1107!--       Inquire number of pavement parameters
1108          CALL get_dimension_length( id_surf, pavement_pars_f%np,              &
1109                                     'npavement_pars' )
1110!
1111!--       Allocate dimension array and input array for pavement parameters
1112          ALLOCATE( pavement_pars_f%pars(0:pavement_pars_f%np-1) )
1113          ALLOCATE( pavement_pars_f%pars_xy(0:pavement_pars_f%np-1,            &
1114                                            nys:nyn,nxl:nxr) )
1115!
1116!--       Get dimension of pavement parameters
1117          CALL get_variable( id_surf, 'npavement_pars', pavement_pars_f%pars )
1118
1119          CALL get_variable( id_surf, 'pavement_pars', pavement_pars_f%pars_xy,&
1120                             nxl, nxr, nys, nyn,                               &
1121                             0, pavement_pars_f%np-1 )
1122       ELSE
1123          pavement_pars_f%from_file = .FALSE.
1124       ENDIF
1125
1126!
1127!--    Read pavement subsurface parameters and related information
1128       IF ( check_existence( var_names, 'pavement_subsurface_pars' ) )         &
1129       THEN
1130          pavement_subsurface_pars_f%from_file = .TRUE.
1131          CALL get_attribute( id_surf, char_fill,                              &
1132                              pavement_subsurface_pars_f%fill,                 &
1133                              .FALSE., 'pavement_subsurface_pars' )
1134!
1135!--       Inquire number of parameters
1136          CALL get_dimension_length( id_surf,                                  &
1137                                     pavement_subsurface_pars_f%np,            &
1138                                     'npavement_subsurface_pars' )
1139!
1140!--       Inquire number of soil layers
1141          CALL get_dimension_length( id_surf,                                  &
1142                                     pavement_subsurface_pars_f%nz,            &
1143                                     'zsoil' )
1144!
1145!--       Allocate dimension array and input array for pavement parameters
1146          ALLOCATE( pavement_subsurface_pars_f%pars                            &
1147                            (0:pavement_subsurface_pars_f%np-1) )
1148          ALLOCATE( pavement_subsurface_pars_f%pars_xyz                        &
1149                            (0:pavement_subsurface_pars_f%np-1,                &
1150                             0:pavement_subsurface_pars_f%nz-1,                &
1151                             nys:nyn,nxl:nxr) )
1152!
1153!--       Get dimension of pavement parameters
1154          CALL get_variable( id_surf, 'npavement_subsurface_pars',             &
1155                             pavement_subsurface_pars_f%pars )
1156
1157          CALL get_variable( id_surf, 'pavement_subsurface_pars',              &
1158                             pavement_subsurface_pars_f%pars_xyz,              &
1159                             nxl, nxr, nys, nyn,                               &
1160                             0, pavement_subsurface_pars_f%nz-1,               &
1161                             0, pavement_subsurface_pars_f%np-1 )
1162       ELSE
1163          pavement_subsurface_pars_f%from_file = .FALSE.
1164       ENDIF
1165
1166
1167!
1168!--    Read vegetation parameters and related information
1169       IF ( check_existence( var_names, 'vegetation_pars' ) )  THEN
1170          vegetation_pars_f%from_file = .TRUE.
1171          CALL get_attribute( id_surf, char_fill,                              &
1172                              vegetation_pars_f%fill,                          &
1173                              .FALSE.,  'vegetation_pars' )
1174!
1175!--       Inquire number of vegetation parameters
1176          CALL get_dimension_length( id_surf, vegetation_pars_f%np,            &
1177                                     'nvegetation_pars' )
1178!
1179!--       Allocate dimension array and input array for surface fractions
1180          ALLOCATE( vegetation_pars_f%pars(0:vegetation_pars_f%np-1) )
1181          ALLOCATE( vegetation_pars_f%pars_xy(0:vegetation_pars_f%np-1,        &
1182                                              nys:nyn,nxl:nxr) )
1183!
1184!--       Get dimension of the parameters
1185          CALL get_variable( id_surf, 'nvegetation_pars',                      &
1186                             vegetation_pars_f%pars )
1187
1188          CALL get_variable( id_surf, 'vegetation_pars',                       &
1189                             vegetation_pars_f%pars_xy, nxl, nxr, nys, nyn,    &
1190                             0, vegetation_pars_f%np-1 )
1191       ELSE
1192          vegetation_pars_f%from_file = .FALSE.
1193       ENDIF
1194
1195!
1196!--    Read root parameters/distribution and related information
1197       IF ( check_existence( var_names, 'soil_pars' ) )  THEN
1198          soil_pars_f%from_file = .TRUE.
1199          CALL get_attribute( id_surf, char_fill,                              &
1200                              soil_pars_f%fill,                                &
1201                              .FALSE., 'soil_pars' )
1202
1203          CALL get_attribute( id_surf, char_lod,                               &
1204                              soil_pars_f%lod,                                 &
1205                              .FALSE., 'soil_pars' )
1206
1207!
1208!--       Inquire number of soil parameters
1209          CALL get_dimension_length( id_surf,                                  &
1210                                     soil_pars_f%np,                           &
1211                                     'nsoil_pars' )
1212!
1213!--       Read parameters array
1214          ALLOCATE( soil_pars_f%pars(0:soil_pars_f%np-1) )
1215          CALL get_variable( id_surf, 'nsoil_pars', soil_pars_f%pars )
1216
1217!
1218!--       In case of level of detail 2, also inquire number of vertical
1219!--       soil layers, allocate memory and read the respective dimension
1220          IF ( soil_pars_f%lod == 2 )  THEN
1221             CALL get_dimension_length( id_surf, soil_pars_f%nz, 'zsoil' )
1222
1223             ALLOCATE( soil_pars_f%layers(0:soil_pars_f%nz-1) )
1224             CALL get_variable( id_surf, 'zsoil', soil_pars_f%layers )
1225
1226          ENDIF
1227
1228!
1229!--       Read soil parameters, depending on level of detail
1230          IF ( soil_pars_f%lod == 1 )  THEN
1231             ALLOCATE( soil_pars_f%pars_xy(0:soil_pars_f%np-1,                 &
1232                                           nys:nyn,nxl:nxr) )
1233                 
1234             CALL get_variable( id_surf, 'soil_pars', soil_pars_f%pars_xy,     &
1235                                nxl, nxr, nys, nyn, 0, soil_pars_f%np-1 )
1236
1237          ELSEIF ( soil_pars_f%lod == 2 )  THEN
1238             ALLOCATE( soil_pars_f%pars_xyz(0:soil_pars_f%np-1,                &
1239                                            0:soil_pars_f%nz-1,                &
1240                                            nys:nyn,nxl:nxr) )
1241             CALL get_variable( id_surf, 'soil_pars',                          &
1242                                soil_pars_f%pars_xyz,                          &
1243                                nxl, nxr, nys, nyn, 0, soil_pars_f%nz-1,       &
1244                                0, soil_pars_f%np-1 )
1245
1246          ENDIF
1247       ELSE
1248          soil_pars_f%from_file = .FALSE.
1249       ENDIF
1250
1251!
1252!--    Read water parameters and related information
1253       IF ( check_existence( var_names, 'water_pars' ) )  THEN
1254          water_pars_f%from_file = .TRUE.
1255          CALL get_attribute( id_surf, char_fill,                              &
1256                              water_pars_f%fill,                               &
1257                              .FALSE., 'water_pars' )
1258!
1259!--       Inquire number of water parameters
1260          CALL get_dimension_length( id_surf,                                  &
1261                                     water_pars_f%np,                          &
1262                                     'nwater_pars' )
1263!
1264!--       Allocate dimension array and input array for water parameters
1265          ALLOCATE( water_pars_f%pars(0:water_pars_f%np-1) )
1266          ALLOCATE( water_pars_f%pars_xy(0:water_pars_f%np-1,                  &
1267                                         nys:nyn,nxl:nxr) )
1268!
1269!--       Get dimension of water parameters
1270          CALL get_variable( id_surf, 'nwater_pars', water_pars_f%pars )
1271
1272          CALL get_variable( id_surf, 'water_pars', water_pars_f%pars_xy,      &
1273                             nxl, nxr, nys, nyn, 0, water_pars_f%np-1 )
1274       ELSE
1275          water_pars_f%from_file = .FALSE.
1276       ENDIF
1277!
1278!--    Read root area density - parametrized vegetation
1279       IF ( check_existence( var_names, 'root_area_dens_s' ) )  THEN
1280          root_area_density_lsm_f%from_file = .TRUE.
1281          CALL get_attribute( id_surf, char_fill,                              &
1282                              root_area_density_lsm_f%fill,                    &
1283                              .FALSE., 'root_area_dens_s' )
1284!
1285!--       Obtain number of soil layers from file and allocate variable
1286          CALL get_dimension_length( id_surf, root_area_density_lsm_f%nz,      &
1287                                     'zsoil' )
1288          ALLOCATE( root_area_density_lsm_f%var                                &
1289                                        (0:root_area_density_lsm_f%nz-1,       &
1290                                         nys:nyn,nxl:nxr) )
1291
1292!
1293!--       Read root-area density
1294          CALL get_variable( id_surf, 'root_area_dens_s',                      &
1295                             root_area_density_lsm_f%var,                      &
1296                             nxl, nxr, nys, nyn,                               &
1297                             0, root_area_density_lsm_f%nz-1 )
1298
1299       ELSE
1300          root_area_density_lsm_f%from_file = .FALSE.
1301       ENDIF
1302!
1303!--    Read street type and street crossing
1304       IF ( check_existence( var_names, 'street_type' ) )  THEN
1305          street_type_f%from_file = .TRUE.
1306          CALL get_attribute( id_surf, char_fill,                              &
1307                              street_type_f%fill, .FALSE.,                     &
1308                              'street_type' )
1309
1310          ALLOCATE ( street_type_f%var(nys:nyn,nxl:nxr)  )
1311         
1312          CALL get_variable( id_surf, 'street_type', street_type_f%var,        &
1313                             nxl, nxr, nys, nyn )
1314       ELSE
1315          street_type_f%from_file = .FALSE.
1316       ENDIF
1317
1318       IF ( check_existence( var_names, 'street_crossing' ) )  THEN
1319          street_crossing_f%from_file = .TRUE.
1320          CALL get_attribute( id_surf, char_fill,                              &
1321                              street_crossing_f%fill, .FALSE.,                 &
1322                              'street_crossing' )
1323
1324          ALLOCATE ( street_crossing_f%var(nys:nyn,nxl:nxr)  )
1325
1326          CALL get_variable( id_surf, 'street_crossing',                       &
1327                             street_crossing_f%var, nxl, nxr, nys, nyn )
1328
1329       ELSE
1330          street_crossing_f%from_file = .FALSE.
1331       ENDIF
1332!
1333!--    Still missing: root_resolved and building_surface_pars.
1334!--    Will be implemented as soon as they are available.
1335
1336!
1337!--    Finally, close input file
1338       CALL close_input_file( id_surf )
1339#endif
1340!
1341!--    End of CPU measurement
1342       CALL cpu_log( log_point_s(82), 'NetCDF input', 'stop' )
1343!
1344!--    Exchange 1 ghost points for surface variables. Please note, ghost point
1345!--    exchange for 3D parameter lists should be revised by using additional
1346!--    MPI datatypes or rewriting exchange_horiz.
1347!--    Moreover, varialbes will be resized in the following, including ghost
1348!--    points.
1349!--    Start with 2D Integer variables. Please note, for 8-bit integer
1350!--    variables must be swapt to 32-bit integer before calling exchange_horiz.
1351       IF ( albedo_type_f%from_file )  THEN
1352          var_exchange_int                  = INT( albedo_type_f%fill, KIND = 1 )
1353          var_exchange_int(nys:nyn,nxl:nxr) =                                  &
1354                            INT( albedo_type_f%var(nys:nyn,nxl:nxr), KIND = 4 )
1355          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
1356          DEALLOCATE( albedo_type_f%var )
1357          ALLOCATE( albedo_type_f%var(nysg:nyng,nxlg:nxrg) )
1358          albedo_type_f%var = INT( var_exchange_int, KIND = 1 )
1359       ENDIF
1360       IF ( pavement_type_f%from_file )  THEN
1361          var_exchange_int                  = INT( pavement_type_f%fill, KIND = 1 )
1362          var_exchange_int(nys:nyn,nxl:nxr) =                                  &
1363                          INT( pavement_type_f%var(nys:nyn,nxl:nxr), KIND = 4 )
1364          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
1365          DEALLOCATE( pavement_type_f%var )
1366          ALLOCATE( pavement_type_f%var(nysg:nyng,nxlg:nxrg) )
1367          pavement_type_f%var = INT( var_exchange_int, KIND = 1 )
1368       ENDIF
1369       IF ( soil_type_f%from_file  .AND.  ALLOCATED( soil_type_f%var_2d ) )  THEN
1370          var_exchange_int                  = INT( soil_type_f%fill, KIND = 1 )
1371          var_exchange_int(nys:nyn,nxl:nxr) =                                  &
1372                            INT( soil_type_f%var_2d(nys:nyn,nxl:nxr), KIND = 4 )
1373          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
1374          DEALLOCATE( soil_type_f%var_2d )
1375          ALLOCATE( soil_type_f%var_2d(nysg:nyng,nxlg:nxrg) )
1376          soil_type_f%var_2d = INT( var_exchange_int, KIND = 1 )
1377       ENDIF
1378       IF ( vegetation_type_f%from_file )  THEN
1379          var_exchange_int                  = INT( vegetation_type_f%fill, KIND = 1 )
1380          var_exchange_int(nys:nyn,nxl:nxr) =                                  &
1381                        INT( vegetation_type_f%var(nys:nyn,nxl:nxr), KIND = 4 )
1382          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
1383          DEALLOCATE( vegetation_type_f%var )
1384          ALLOCATE( vegetation_type_f%var(nysg:nyng,nxlg:nxrg) )
1385          vegetation_type_f%var = INT( var_exchange_int, KIND = 1 )
1386       ENDIF
1387       IF ( water_type_f%from_file )  THEN
1388          var_exchange_int                  = INT( water_type_f%fill, KIND = 1 )
1389          var_exchange_int(nys:nyn,nxl:nxr) =                                  &
1390                         INT( water_type_f%var(nys:nyn,nxl:nxr), KIND = 4 )
1391          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
1392          DEALLOCATE( water_type_f%var )
1393          ALLOCATE( water_type_f%var(nysg:nyng,nxlg:nxrg) )
1394          water_type_f%var = INT( var_exchange_int, KIND = 1 )
1395       ENDIF
1396!
1397!--    Exchange 1 ghost point for 3/4-D variables. For the sake of simplicity,
1398!--    loop further dimensions to use 2D exchange routines.
1399!--    This should be revised later by introducing new MPI datatypes.
1400       IF ( soil_type_f%from_file  .AND.  ALLOCATED( soil_type_f%var_3d ) )    &
1401       THEN
1402          ALLOCATE( var_dum_int_3d(0:nz_soil,nys:nyn,nxl:nxr) )
1403          var_dum_int_3d = soil_type_f%var_3d
1404          DEALLOCATE( soil_type_f%var_3d )
1405          ALLOCATE( soil_type_f%var_3d(0:nz_soil,nysg:nyng,nxlg:nxrg) )
1406          soil_type_f%var_3d = soil_type_f%fill
1407
1408          DO  k = 0, nz_soil
1409             var_exchange_int(nys:nyn,nxl:nxr) = var_dum_int_3d(k,nys:nyn,nxl:nxr)
1410             CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
1411             soil_type_f%var_3d(k,:,:) = INT( var_exchange_int(:,:), KIND = 1 )
1412          ENDDO
1413          DEALLOCATE( var_dum_int_3d )
1414       ENDIF
1415
1416       IF ( surface_fraction_f%from_file )  THEN
1417          ALLOCATE( var_dum_real_3d(0:surface_fraction_f%nf-1,nys:nyn,nxl:nxr) )
1418          var_dum_real_3d = surface_fraction_f%frac
1419          DEALLOCATE( surface_fraction_f%frac )
1420          ALLOCATE( surface_fraction_f%frac(0:surface_fraction_f%nf-1,         &
1421                                            nysg:nyng,nxlg:nxrg) )
1422          surface_fraction_f%frac = surface_fraction_f%fill
1423
1424          DO  k = 0, surface_fraction_f%nf-1
1425             var_exchange_real(nys:nyn,nxl:nxr) = var_dum_real_3d(k,nys:nyn,nxl:nxr)
1426             CALL exchange_horiz_2d( var_exchange_real, nbgp )
1427             surface_fraction_f%frac(k,:,:) = var_exchange_real(:,:)
1428          ENDDO
1429          DEALLOCATE( var_dum_real_3d )
1430       ENDIF
1431
1432       IF ( building_pars_f%from_file )  THEN
1433          ALLOCATE( var_dum_real_3d(0:building_pars_f%np-1,nys:nyn,nxl:nxr) )
1434          var_dum_real_3d = building_pars_f%pars_xy
1435          DEALLOCATE( building_pars_f%pars_xy )
1436          ALLOCATE( building_pars_f%pars_xy(0:building_pars_f%np-1,            &
1437                                            nysg:nyng,nxlg:nxrg) )
1438          building_pars_f%pars_xy = building_pars_f%fill
1439          DO  k = 0, building_pars_f%np-1
1440             var_exchange_real(nys:nyn,nxl:nxr) =                              &
1441                                              var_dum_real_3d(k,nys:nyn,nxl:nxr)
1442             CALL exchange_horiz_2d( var_exchange_real, nbgp )
1443             building_pars_f%pars_xy(k,:,:) = var_exchange_real(:,:)
1444          ENDDO
1445          DEALLOCATE( var_dum_real_3d )
1446       ENDIF
1447
1448       IF ( albedo_pars_f%from_file )  THEN
1449          ALLOCATE( var_dum_real_3d(0:albedo_pars_f%np-1,nys:nyn,nxl:nxr) )
1450          var_dum_real_3d = albedo_pars_f%pars_xy
1451          DEALLOCATE( albedo_pars_f%pars_xy )
1452          ALLOCATE( albedo_pars_f%pars_xy(0:albedo_pars_f%np-1,                &
1453                                          nysg:nyng,nxlg:nxrg) )
1454          albedo_pars_f%pars_xy = albedo_pars_f%fill
1455          DO  k = 0, albedo_pars_f%np-1
1456             var_exchange_real(nys:nyn,nxl:nxr) =                              &
1457                                              var_dum_real_3d(k,nys:nyn,nxl:nxr)
1458             CALL exchange_horiz_2d( var_exchange_real, nbgp )
1459             albedo_pars_f%pars_xy(k,:,:) = var_exchange_real(:,:)
1460          ENDDO
1461          DEALLOCATE( var_dum_real_3d )
1462       ENDIF
1463
1464       IF ( pavement_pars_f%from_file )  THEN
1465          ALLOCATE( var_dum_real_3d(0:pavement_pars_f%np-1,nys:nyn,nxl:nxr) )
1466          var_dum_real_3d = pavement_pars_f%pars_xy
1467          DEALLOCATE( pavement_pars_f%pars_xy )
1468          ALLOCATE( pavement_pars_f%pars_xy(0:pavement_pars_f%np-1,            &
1469                                            nysg:nyng,nxlg:nxrg) )
1470          pavement_pars_f%pars_xy = pavement_pars_f%fill
1471          DO  k = 0, pavement_pars_f%np-1
1472             var_exchange_real(nys:nyn,nxl:nxr) =                              &
1473                                              var_dum_real_3d(k,nys:nyn,nxl:nxr)
1474             CALL exchange_horiz_2d( var_exchange_real, nbgp )
1475             pavement_pars_f%pars_xy(k,:,:) = var_exchange_real(:,:)
1476          ENDDO
1477          DEALLOCATE( var_dum_real_3d )
1478       ENDIF
1479
1480       IF ( vegetation_pars_f%from_file )  THEN
1481          ALLOCATE( var_dum_real_3d(0:vegetation_pars_f%np-1,nys:nyn,nxl:nxr) )
1482          var_dum_real_3d = vegetation_pars_f%pars_xy
1483          DEALLOCATE( vegetation_pars_f%pars_xy )
1484          ALLOCATE( vegetation_pars_f%pars_xy(0:vegetation_pars_f%np-1,        &
1485                                            nysg:nyng,nxlg:nxrg) )
1486          vegetation_pars_f%pars_xy = vegetation_pars_f%fill
1487          DO  k = 0, vegetation_pars_f%np-1
1488             var_exchange_real(nys:nyn,nxl:nxr) =                              &
1489                                              var_dum_real_3d(k,nys:nyn,nxl:nxr)
1490             CALL exchange_horiz_2d( var_exchange_real, nbgp )
1491             vegetation_pars_f%pars_xy(k,:,:) = var_exchange_real(:,:)
1492          ENDDO
1493          DEALLOCATE( var_dum_real_3d )
1494       ENDIF
1495
1496       IF ( water_pars_f%from_file )  THEN
1497          ALLOCATE( var_dum_real_3d(0:water_pars_f%np-1,nys:nyn,nxl:nxr) )
1498          var_dum_real_3d = water_pars_f%pars_xy
1499          DEALLOCATE( water_pars_f%pars_xy )
1500          ALLOCATE( water_pars_f%pars_xy(0:water_pars_f%np-1,                  &
1501                                         nysg:nyng,nxlg:nxrg) )
1502          water_pars_f%pars_xy = water_pars_f%fill
1503          DO  k = 0, water_pars_f%np-1
1504             var_exchange_real(nys:nyn,nxl:nxr) =                              &
1505                                              var_dum_real_3d(k,nys:nyn,nxl:nxr)
1506             CALL exchange_horiz_2d( var_exchange_real, nbgp )
1507             water_pars_f%pars_xy(k,:,:) = var_exchange_real(:,:)
1508          ENDDO
1509          DEALLOCATE( var_dum_real_3d )
1510       ENDIF
1511
1512       IF ( root_area_density_lsm_f%from_file )  THEN
1513          ALLOCATE( var_dum_real_3d(0:root_area_density_lsm_f%nz-1,nys:nyn,nxl:nxr) )
1514          var_dum_real_3d = root_area_density_lsm_f%var
1515          DEALLOCATE( root_area_density_lsm_f%var )
1516          ALLOCATE( root_area_density_lsm_f%var(0:root_area_density_lsm_f%nz-1,&
1517                                                nysg:nyng,nxlg:nxrg) )
1518          root_area_density_lsm_f%var = root_area_density_lsm_f%fill
1519
1520          DO  k = 0, root_area_density_lsm_f%nz-1
1521             var_exchange_real(nys:nyn,nxl:nxr) =                              &
1522                                              var_dum_real_3d(k,nys:nyn,nxl:nxr)
1523             CALL exchange_horiz_2d( var_exchange_real, nbgp )
1524             root_area_density_lsm_f%var(k,:,:) = var_exchange_real(:,:)
1525          ENDDO
1526          DEALLOCATE( var_dum_real_3d )
1527       ENDIF
1528
1529       IF ( soil_pars_f%from_file )  THEN
1530          IF ( soil_pars_f%lod == 1 )  THEN
1531
1532             ALLOCATE( var_dum_real_3d(0:soil_pars_f%np-1,nys:nyn,nxl:nxr) )
1533             var_dum_real_3d = soil_pars_f%pars_xy
1534             DEALLOCATE( soil_pars_f%pars_xy )
1535             ALLOCATE( soil_pars_f%pars_xy(0:soil_pars_f%np-1,                 &
1536                                            nysg:nyng,nxlg:nxrg) )
1537             soil_pars_f%pars_xy = soil_pars_f%fill
1538
1539             DO  k = 0, soil_pars_f%np-1
1540                var_exchange_real(nys:nyn,nxl:nxr) =                           &
1541                                              var_dum_real_3d(k,nys:nyn,nxl:nxr)
1542                CALL exchange_horiz_2d( var_exchange_real, nbgp )
1543                soil_pars_f%pars_xy(k,:,:) = var_exchange_real(:,:)
1544             ENDDO
1545             DEALLOCATE( var_dum_real_3d )
1546          ELSEIF ( soil_pars_f%lod == 2 )  THEN
1547             ALLOCATE( var_dum_real_4d(0:soil_pars_f%np-1,                     &
1548                                       0:soil_pars_f%nz-1,                     &
1549                                       nys:nyn,nxl:nxr) )
1550             var_dum_real_4d = soil_pars_f%pars_xyz
1551             DEALLOCATE( soil_pars_f%pars_xyz )
1552             ALLOCATE( soil_pars_f%pars_xyz(0:soil_pars_f%np-1,                &
1553                                            0:soil_pars_f%nz-1,                &
1554                                            nysg:nyng,nxlg:nxrg) )
1555             soil_pars_f%pars_xyz = soil_pars_f%fill
1556
1557             DO  k2 = 0, soil_pars_f%nz-1
1558                DO  k = 0, soil_pars_f%np-1
1559                   var_exchange_real(nys:nyn,nxl:nxr) =                        &
1560                                           var_dum_real_4d(k,k2,nys:nyn,nxl:nxr)
1561                   CALL exchange_horiz_2d( var_exchange_real, nbgp )
1562
1563                   soil_pars_f%pars_xyz(k,k2,:,:) = var_exchange_real(:,:)
1564                ENDDO
1565             ENDDO
1566             DEALLOCATE( var_dum_real_4d )
1567          ENDIF
1568       ENDIF
1569
1570       IF ( pavement_subsurface_pars_f%from_file )  THEN
1571          ALLOCATE( var_dum_real_4d(0:pavement_subsurface_pars_f%np-1,         &
1572                                    0:pavement_subsurface_pars_f%nz-1,         &
1573                                    nys:nyn,nxl:nxr) )
1574          var_dum_real_4d = pavement_subsurface_pars_f%pars_xyz
1575          DEALLOCATE( pavement_subsurface_pars_f%pars_xyz )
1576          ALLOCATE( pavement_subsurface_pars_f%pars_xyz                        &
1577                                          (0:pavement_subsurface_pars_f%np-1,  &
1578                                           0:pavement_subsurface_pars_f%nz-1,  &
1579                                           nysg:nyng,nxlg:nxrg) )
1580          pavement_subsurface_pars_f%pars_xyz = pavement_subsurface_pars_f%fill
1581
1582          DO  k2 = 0, pavement_subsurface_pars_f%nz-1
1583             DO  k = 0, pavement_subsurface_pars_f%np-1
1584                var_exchange_real(nys:nyn,nxl:nxr) =                           &
1585                                          var_dum_real_4d(k,k2,nys:nyn,nxl:nxr)
1586                CALL exchange_horiz_2d( var_exchange_real, nbgp )
1587                pavement_subsurface_pars_f%pars_xyz(k,k2,:,:) =                &
1588                                                        var_exchange_real(:,:)
1589             ENDDO
1590          ENDDO
1591          DEALLOCATE( var_dum_real_4d )
1592       ENDIF
1593
1594!
1595!--    In case of non-cyclic boundary conditions, set Neumann conditions at the
1596!--    lateral boundaries.
1597       IF ( .NOT. bc_ns_cyc )  THEN
1598          IF ( nys == 0  )  THEN
1599             IF ( albedo_type_f%from_file )                                    &
1600                albedo_type_f%var(-1,:) = albedo_type_f%var(0,:)
1601             IF ( pavement_type_f%from_file )                                  &
1602                pavement_type_f%var(-1,:) = pavement_type_f%var(0,:)
1603             IF ( soil_type_f%from_file )  THEN
1604                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
1605                   soil_type_f%var_2d(-1,:) = soil_type_f%var_2d(0,:)
1606                ELSE
1607                   soil_type_f%var_3d(:,-1,:) = soil_type_f%var_3d(:,0,:)
1608                ENDIF
1609             ENDIF
1610             IF ( vegetation_type_f%from_file )                                &
1611                vegetation_type_f%var(-1,:) = vegetation_type_f%var(0,:)
1612             IF ( water_type_f%from_file )                                     &
1613                water_type_f%var(-1,:) = water_type_f%var(0,:)
1614             IF ( surface_fraction_f%from_file )                               &
1615                surface_fraction_f%frac(:,-1,:) = surface_fraction_f%frac(:,0,:)
1616             IF ( building_pars_f%from_file )                                  &
1617                building_pars_f%pars_xy(:,-1,:) = building_pars_f%pars_xy(:,0,:)
1618             IF ( albedo_pars_f%from_file )                                    &
1619                albedo_pars_f%pars_xy(:,-1,:) = albedo_pars_f%pars_xy(:,0,:)
1620             IF ( pavement_pars_f%from_file )                                  &
1621                pavement_pars_f%pars_xy(:,-1,:) = pavement_pars_f%pars_xy(:,0,:)
1622             IF ( vegetation_pars_f%from_file )                                &
1623                vegetation_pars_f%pars_xy(:,-1,:) =                            &
1624                                               vegetation_pars_f%pars_xy(:,0,:)
1625             IF ( water_pars_f%from_file )                                     &
1626                water_pars_f%pars_xy(:,-1,:) = water_pars_f%pars_xy(:,0,:)
1627             IF ( root_area_density_lsm_f%from_file )                          &
1628                root_area_density_lsm_f%var(:,-1,:) =                          &
1629                                            root_area_density_lsm_f%var(:,0,:)
1630             IF ( soil_pars_f%from_file )  THEN
1631                IF ( soil_pars_f%lod == 1 )  THEN
1632                   soil_pars_f%pars_xy(:,-1,:) = soil_pars_f%pars_xy(:,0,:)
1633                ELSE
1634                   soil_pars_f%pars_xyz(:,:,-1,:) = soil_pars_f%pars_xyz(:,:,0,:)
1635                ENDIF
1636             ENDIF
1637             IF ( pavement_subsurface_pars_f%from_file )                       &
1638                pavement_subsurface_pars_f%pars_xyz(:,:,-1,:) =                &
1639                                   pavement_subsurface_pars_f%pars_xyz(:,:,0,:)
1640          ENDIF
1641
1642          IF ( nyn == ny )  THEN
1643             IF ( albedo_type_f%from_file )                                    &
1644                albedo_type_f%var(ny+1,:) = albedo_type_f%var(ny,:)
1645             IF ( pavement_type_f%from_file )                                  &
1646                pavement_type_f%var(ny+1,:) = pavement_type_f%var(ny,:)
1647             IF ( soil_type_f%from_file )  THEN
1648                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
1649                   soil_type_f%var_2d(ny+1,:) = soil_type_f%var_2d(ny,:)
1650                ELSE
1651                   soil_type_f%var_3d(:,ny+1,:) = soil_type_f%var_3d(:,ny,:)
1652                ENDIF
1653             ENDIF
1654             IF ( vegetation_type_f%from_file )                                &
1655                vegetation_type_f%var(ny+1,:) = vegetation_type_f%var(ny,:)
1656             IF ( water_type_f%from_file )                                     &
1657                water_type_f%var(ny+1,:) = water_type_f%var(ny,:)
1658             IF ( surface_fraction_f%from_file )                               &
1659                surface_fraction_f%frac(:,ny+1,:) =                            &
1660                                             surface_fraction_f%frac(:,ny,:)
1661             IF ( building_pars_f%from_file )                                  &
1662                building_pars_f%pars_xy(:,ny+1,:) =                            &
1663                                             building_pars_f%pars_xy(:,ny,:)
1664             IF ( albedo_pars_f%from_file )                                    &
1665                albedo_pars_f%pars_xy(:,ny+1,:) = albedo_pars_f%pars_xy(:,ny,:)
1666             IF ( pavement_pars_f%from_file )                                  &
1667                pavement_pars_f%pars_xy(:,ny+1,:) =                            &
1668                                             pavement_pars_f%pars_xy(:,ny,:)
1669             IF ( vegetation_pars_f%from_file )                                &
1670                vegetation_pars_f%pars_xy(:,ny+1,:) =                          &
1671                                               vegetation_pars_f%pars_xy(:,ny,:)
1672             IF ( water_pars_f%from_file )                                     &
1673                water_pars_f%pars_xy(:,ny+1,:) = water_pars_f%pars_xy(:,ny,:)
1674             IF ( root_area_density_lsm_f%from_file )                          &
1675                root_area_density_lsm_f%var(:,ny+1,:) =                        &
1676                                            root_area_density_lsm_f%var(:,ny,:)
1677             IF ( soil_pars_f%from_file )  THEN
1678                IF ( soil_pars_f%lod == 1 )  THEN
1679                   soil_pars_f%pars_xy(:,ny+1,:) = soil_pars_f%pars_xy(:,ny,:)
1680                ELSE
1681                   soil_pars_f%pars_xyz(:,:,ny+1,:) =                          &
1682                                              soil_pars_f%pars_xyz(:,:,ny,:)
1683                ENDIF
1684             ENDIF
1685             IF ( pavement_subsurface_pars_f%from_file )                       &
1686                pavement_subsurface_pars_f%pars_xyz(:,:,ny+1,:) =              &
1687                                   pavement_subsurface_pars_f%pars_xyz(:,:,ny,:)
1688          ENDIF
1689       ENDIF
1690
1691       IF ( .NOT. bc_lr_cyc )  THEN
1692          IF ( nxl == 0 )  THEN
1693            IF ( albedo_type_f%from_file )                                     &
1694                albedo_type_f%var(:,-1) = albedo_type_f%var(:,0)
1695             IF ( pavement_type_f%from_file )                                  &
1696                pavement_type_f%var(:,-1) = pavement_type_f%var(:,0)
1697             IF ( soil_type_f%from_file )  THEN
1698                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
1699                   soil_type_f%var_2d(:,-1) = soil_type_f%var_2d(:,0)
1700                ELSE
1701                   soil_type_f%var_3d(:,:,-1) = soil_type_f%var_3d(:,:,0)
1702                ENDIF
1703             ENDIF
1704             IF ( vegetation_type_f%from_file )                                &
1705                vegetation_type_f%var(:,-1) = vegetation_type_f%var(:,0)
1706             IF ( water_type_f%from_file )                                     &
1707                water_type_f%var(:,-1) = water_type_f%var(:,0)
1708             IF ( surface_fraction_f%from_file )                               &
1709                surface_fraction_f%frac(:,:,-1) = surface_fraction_f%frac(:,:,0)
1710             IF ( building_pars_f%from_file )                                  &
1711                building_pars_f%pars_xy(:,:,-1) = building_pars_f%pars_xy(:,:,0)
1712             IF ( albedo_pars_f%from_file )                                    &
1713                albedo_pars_f%pars_xy(:,:,-1) = albedo_pars_f%pars_xy(:,:,0)
1714             IF ( pavement_pars_f%from_file )                                  &
1715                pavement_pars_f%pars_xy(:,:,-1) = pavement_pars_f%pars_xy(:,:,0)
1716             IF ( vegetation_pars_f%from_file )                                &
1717                vegetation_pars_f%pars_xy(:,:,-1) =                            &
1718                                               vegetation_pars_f%pars_xy(:,:,0)
1719             IF ( water_pars_f%from_file )                                     &
1720                water_pars_f%pars_xy(:,:,-1) = water_pars_f%pars_xy(:,:,0)
1721             IF ( root_area_density_lsm_f%from_file )                          &
1722                root_area_density_lsm_f%var(:,:,-1) =                          &
1723                                            root_area_density_lsm_f%var(:,:,0)
1724             IF ( soil_pars_f%from_file )  THEN
1725                IF ( soil_pars_f%lod == 1 )  THEN
1726                   soil_pars_f%pars_xy(:,:,-1) = soil_pars_f%pars_xy(:,:,0)
1727                ELSE
1728                   soil_pars_f%pars_xyz(:,:,:,-1) = soil_pars_f%pars_xyz(:,:,:,0)
1729                ENDIF
1730             ENDIF
1731             IF ( pavement_subsurface_pars_f%from_file )                       &
1732                pavement_subsurface_pars_f%pars_xyz(:,:,:,-1) =                &
1733                                    pavement_subsurface_pars_f%pars_xyz(:,:,:,0)
1734          ENDIF
1735
1736          IF ( nxr == nx )  THEN
1737             IF ( albedo_type_f%from_file )                                    &
1738                albedo_type_f%var(:,nx+1) = albedo_type_f%var(:,nx)
1739             IF ( pavement_type_f%from_file )                                  &
1740                pavement_type_f%var(:,nx+1) = pavement_type_f%var(:,nx)
1741             IF ( soil_type_f%from_file )  THEN
1742                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
1743                   soil_type_f%var_2d(:,nx+1) = soil_type_f%var_2d(:,nx)
1744                ELSE
1745                   soil_type_f%var_3d(:,:,nx+1) = soil_type_f%var_3d(:,:,nx)
1746                ENDIF
1747             ENDIF
1748             IF ( vegetation_type_f%from_file )                                &
1749                vegetation_type_f%var(:,nx+1) = vegetation_type_f%var(:,nx)
1750             IF ( water_type_f%from_file )                                     &
1751                water_type_f%var(:,nx+1) = water_type_f%var(:,nx)
1752             IF ( surface_fraction_f%from_file )                               &
1753                surface_fraction_f%frac(:,:,nx+1) =                            &
1754                                             surface_fraction_f%frac(:,:,nx)
1755             IF ( building_pars_f%from_file )                                  &
1756                building_pars_f%pars_xy(:,:,nx+1) =                            &
1757                                             building_pars_f%pars_xy(:,:,nx)
1758             IF ( albedo_pars_f%from_file )                                    &
1759                albedo_pars_f%pars_xy(:,:,nx+1) = albedo_pars_f%pars_xy(:,:,nx)
1760             IF ( pavement_pars_f%from_file )                                  &
1761                pavement_pars_f%pars_xy(:,:,nx+1) =                            &
1762                                             pavement_pars_f%pars_xy(:,:,nx)
1763             IF ( vegetation_pars_f%from_file )                                &
1764                vegetation_pars_f%pars_xy(:,:,nx+1) =                          &
1765                                               vegetation_pars_f%pars_xy(:,:,nx)
1766             IF ( water_pars_f%from_file )                                     &
1767                water_pars_f%pars_xy(:,:,nx+1) = water_pars_f%pars_xy(:,:,nx)
1768             IF ( root_area_density_lsm_f%from_file )                          &
1769                root_area_density_lsm_f%var(:,:,nx+1) =                        &
1770                                            root_area_density_lsm_f%var(:,:,nx)
1771             IF ( soil_pars_f%from_file )  THEN
1772                IF ( soil_pars_f%lod == 1 )  THEN
1773                   soil_pars_f%pars_xy(:,:,nx+1) = soil_pars_f%pars_xy(:,:,nx)
1774                ELSE
1775                   soil_pars_f%pars_xyz(:,:,:,nx+1) =                          &
1776                                              soil_pars_f%pars_xyz(:,:,:,nx)
1777                ENDIF
1778             ENDIF
1779             IF ( pavement_subsurface_pars_f%from_file )                       &
1780                pavement_subsurface_pars_f%pars_xyz(:,:,:,nx+1) =              &
1781                                   pavement_subsurface_pars_f%pars_xyz(:,:,:,nx)
1782          ENDIF
1783       ENDIF
1784
1785    END SUBROUTINE netcdf_data_input_surface_data
1786
1787!------------------------------------------------------------------------------!
1788! Description:
1789! ------------
1790!> Reads orography and building information.
1791!------------------------------------------------------------------------------!
1792    SUBROUTINE netcdf_data_input_topo
1793
1794       USE control_parameters,                                                 &
1795           ONLY:  bc_lr_cyc, bc_ns_cyc, message_string, topography
1796
1797       USE indices,                                                            &
1798           ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb
1799
1800
1801       IMPLICIT NONE
1802
1803       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names in static input file
1804
1805
1806       INTEGER(iwp) ::  i             !< running index along x-direction
1807       INTEGER(iwp) ::  ii            !< running index for IO blocks
1808       INTEGER(iwp) ::  id_topo       !< NetCDF id of topograhy input file
1809       INTEGER(iwp) ::  j             !< running index along y-direction
1810       INTEGER(iwp) ::  num_vars      !< number of variables in netcdf input file
1811       INTEGER(iwp) ::  skip_n_rows   !< counting variable to skip rows while reading topography file
1812
1813       INTEGER(iwp), DIMENSION(nys-nbgp:nyn+nbgp,nxl-nbgp:nxr+nbgp) ::  var_exchange_int !< dummy variables used to exchange 32-bit Integer arrays
1814
1815       REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file
1816!
1817!--    CPU measurement
1818       CALL cpu_log( log_point_s(83), 'NetCDF/ASCII input topo', 'start' )
1819
1820!
1821!--    Input via palm-input data standard
1822       IF ( input_pids_static )  THEN
1823#if defined ( __netcdf )
1824!
1825!--       Open file in read-only mode
1826          CALL open_read_file( TRIM( input_file_static ) //                    &
1827                               TRIM( coupling_char ), id_topo )
1828!
1829!--       At first, inquire all variable names.
1830!--       This will be used to check whether an  input variable exist
1831!--       or not.
1832          CALL inquire_num_variables( id_topo, num_vars )
1833!
1834!--       Allocate memory to store variable names and inquire them.
1835          ALLOCATE( var_names(1:num_vars) )
1836          CALL inquire_variable_names( id_topo, var_names )
1837!
1838!--       Read x, y - dimensions. Only required for consistency checks.
1839          CALL get_dimension_length( id_topo, dim_static%nx, 'x' )
1840          CALL get_dimension_length( id_topo, dim_static%ny, 'y' )
1841          ALLOCATE( dim_static%x(0:dim_static%nx-1) )
1842          ALLOCATE( dim_static%y(0:dim_static%ny-1) )
1843          CALL get_variable( id_topo, 'x', dim_static%x )
1844          CALL get_variable( id_topo, 'y', dim_static%y )
1845!
1846!--       Terrain height. First, get variable-related _FillValue attribute
1847          IF ( check_existence( var_names, 'zt' ) )  THEN
1848             terrain_height_f%from_file = .TRUE.
1849             CALL get_attribute( id_topo, char_fill, terrain_height_f%fill,    &
1850                                 .FALSE., 'zt' )
1851!
1852!--          Input 2D terrain height.
1853             ALLOCATE ( terrain_height_f%var(nys:nyn,nxl:nxr)  )
1854             
1855             CALL get_variable( id_topo, 'zt', terrain_height_f%var,           &
1856                                nxl, nxr, nys, nyn )
1857
1858          ELSE
1859             terrain_height_f%from_file = .FALSE.
1860          ENDIF
1861
1862!
1863!--       Read building height. First, read its _FillValue attribute,
1864!--       as well as lod attribute
1865          buildings_f%from_file = .FALSE.
1866          IF ( check_existence( var_names, 'buildings_2d' ) )  THEN
1867             buildings_f%from_file = .TRUE.
1868             CALL get_attribute( id_topo, char_lod, buildings_f%lod,           &
1869                                 .FALSE., 'buildings_2d' )
1870
1871             CALL get_attribute( id_topo, char_fill, buildings_f%fill1,        &
1872                                 .FALSE., 'buildings_2d' )
1873
1874!
1875!--          Read 2D buildings
1876             IF ( buildings_f%lod == 1 )  THEN
1877                ALLOCATE ( buildings_f%var_2d(nys:nyn,nxl:nxr) )
1878
1879                CALL get_variable( id_topo, 'buildings_2d',                    &
1880                                   buildings_f%var_2d,                         &
1881                                   nxl, nxr, nys, nyn )
1882             ELSE
1883                message_string = 'NetCDF attribute lod ' //                    &
1884                                 '(level of detail) is not set ' //            &
1885                                 'properly for buildings_2d.'
1886                CALL message( 'netcdf_data_input_mod', 'PA0540',               &
1887                               1, 2, 0, 6, 0 )
1888             ENDIF
1889          ENDIF
1890!
1891!--       If available, also read 3D building information. If both are
1892!--       available, use 3D information.
1893          IF ( check_existence( var_names, 'buildings_3d' ) )  THEN
1894             buildings_f%from_file = .TRUE.
1895             CALL get_attribute( id_topo, char_lod, buildings_f%lod,           &
1896                                 .FALSE., 'buildings_3d' )     
1897
1898             CALL get_attribute( id_topo, char_fill, buildings_f%fill2,        &
1899                                 .FALSE., 'buildings_3d' )
1900
1901             CALL get_dimension_length( id_topo, buildings_f%nz, 'z' )
1902!
1903!--          Read 3D buildings
1904             IF ( buildings_f%lod == 2 )  THEN
1905                ALLOCATE( buildings_f%z(nzb:buildings_f%nz-1) )
1906                CALL get_variable( id_topo, 'z', buildings_f%z )
1907
1908                ALLOCATE( buildings_f%var_3d(nzb:buildings_f%nz-1,             &
1909                                             nys:nyn,nxl:nxr) )
1910                buildings_f%var_3d = 0
1911               
1912                CALL get_variable( id_topo, 'buildings_3d',                    &
1913                                   buildings_f%var_3d,                         &
1914                                   nxl, nxr, nys, nyn, 0, buildings_f%nz-1 )
1915             ELSE
1916                message_string = 'NetCDF attribute lod ' //                    &
1917                                 '(level of detail) is not set ' //            &
1918                                 'properly for buildings_3d.'
1919                CALL message( 'netcdf_data_input_mod', 'PA0541',               &
1920                               1, 2, 0, 6, 0 )
1921             ENDIF
1922          ENDIF
1923!
1924!--       Read building IDs and its FillValue attribute. Further required
1925!--       for mapping buildings on top of orography.
1926          IF ( check_existence( var_names, 'building_id' ) )  THEN
1927             building_id_f%from_file = .TRUE.
1928             CALL get_attribute( id_topo, char_fill,                           &
1929                                 building_id_f%fill, .FALSE.,                  &
1930                                 'building_id' )
1931
1932             ALLOCATE ( building_id_f%var(nys:nyn,nxl:nxr) )
1933             
1934             CALL get_variable( id_topo, 'building_id', building_id_f%var,     &
1935                                nxl, nxr, nys, nyn )
1936          ELSE
1937             building_id_f%from_file = .FALSE.
1938          ENDIF
1939!
1940!--       Read building_type and required attributes.
1941          IF ( check_existence( var_names, 'building_type' ) )  THEN
1942             building_type_f%from_file = .TRUE.
1943             CALL get_attribute( id_topo, char_fill,                           &
1944                                 building_type_f%fill, .FALSE.,                &
1945                                 'building_type' )
1946
1947             ALLOCATE ( building_type_f%var(nys:nyn,nxl:nxr) )
1948
1949             CALL get_variable( id_topo, 'building_type', building_type_f%var, &
1950                                nxl, nxr, nys, nyn )
1951
1952          ELSE
1953             building_type_f%from_file = .FALSE.
1954          ENDIF
1955!
1956!--       Close topography input file
1957          CALL close_input_file( id_topo )
1958#else
1959          CONTINUE
1960#endif
1961!
1962!--    ASCII input
1963       ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
1964             
1965          DO  ii = 0, io_blocks-1
1966             IF ( ii == io_group )  THEN
1967
1968                OPEN( 90, FILE='TOPOGRAPHY_DATA'//TRIM( coupling_char ),       &
1969                      STATUS='OLD', FORM='FORMATTED', ERR=10 )
1970!
1971!--             Read topography PE-wise. Rows are read from nyn to nys, columns
1972!--             are read from nxl to nxr. At first, ny-nyn rows need to be skipped.
1973                skip_n_rows = 0
1974                DO WHILE ( skip_n_rows < ny - nyn )
1975                   READ( 90, * )
1976                   skip_n_rows = skip_n_rows + 1
1977                ENDDO
1978!
1979!--             Read data from nyn to nys and nxl to nxr. Therefore, skip
1980!--             column until nxl-1 is reached
1981                ALLOCATE ( buildings_f%var_2d(nys:nyn,nxl:nxr) )
1982                DO  j = nyn, nys, -1
1983                   READ( 90, *, ERR=11, END=11 )                               &
1984                                   ( dum, i = 0, nxl-1 ),                      &
1985                                   ( buildings_f%var_2d(j,i), i = nxl, nxr )
1986                ENDDO
1987
1988                GOTO 12
1989
1990 10             message_string = 'file TOPOGRAPHY_DATA'//                      &
1991                                 TRIM( coupling_char )// ' does not exist'
1992                CALL message( 'netcdf_data_input_mod', 'PA0208', 1, 2, 0, 6, 0 )
1993
1994 11             message_string = 'errors in file TOPOGRAPHY_DATA'//            &
1995                                 TRIM( coupling_char )
1996                CALL message( 'netcdf_data_input_mod', 'PA0209', 2, 2, 0, 6, 0 )
1997
1998 12             CLOSE( 90 )
1999                buildings_f%from_file = .TRUE.
2000
2001             ENDIF
2002#if defined( __parallel )
2003             CALL MPI_BARRIER( comm2d, ierr )
2004#endif
2005          ENDDO
2006
2007       ENDIF
2008!
2009!--    End of CPU measurement
2010       CALL cpu_log( log_point_s(83), 'NetCDF/ASCII input topo', 'stop' )
2011!
2012!--    Check for minimum requirement to setup building topography. If buildings
2013!--    are provided, also an ID and a type are required.
2014!--    Note, doing this check in check_parameters
2015!--    will be too late (data will be used for grid inititialization before).
2016       IF ( input_pids_static )  THEN
2017          IF ( buildings_f%from_file  .AND.                                    &
2018               .NOT. building_id_f%from_file )  THEN
2019             message_string = 'If building heigths are prescribed in ' //      &
2020                              'static input file, also an ID is required.'
2021             CALL message( 'netcdf_data_input_mod', 'PA0542', 1, 2, 0, 6, 0 )
2022          ENDIF
2023       ENDIF
2024!
2025!--    In case no terrain height is provided by static input file, allocate
2026!--    array nevertheless and set terrain height to 0, which simplifies
2027!--    topography initialization.
2028       IF ( .NOT. terrain_height_f%from_file )  THEN
2029          ALLOCATE ( terrain_height_f%var(nys:nyn,nxl:nxr) )
2030          terrain_height_f%var = 0.0_wp
2031       ENDIF
2032!
2033!--    Finally, exchange 1 ghost point for building ID and type.
2034!--    In case of non-cyclic boundary conditions set Neumann conditions at the
2035!--    lateral boundaries.
2036       IF ( building_id_f%from_file )  THEN
2037          var_exchange_int                  = building_id_f%fill
2038          var_exchange_int(nys:nyn,nxl:nxr) = building_id_f%var(nys:nyn,nxl:nxr)
2039          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
2040          DEALLOCATE( building_id_f%var )
2041          ALLOCATE( building_id_f%var(nys-nbgp:nyn+nbgp,nxl-nbgp:nxr+nbgp) )
2042          building_id_f%var = var_exchange_int
2043
2044          IF ( .NOT. bc_ns_cyc )  THEN
2045             IF ( nys == 0  )  building_id_f%var(-1,:)   = building_id_f%var(0,:)
2046             IF ( nyn == ny )  building_id_f%var(ny+1,:) = building_id_f%var(ny,:)
2047          ENDIF
2048          IF ( .NOT. bc_lr_cyc )  THEN
2049             IF ( nxl == 0  )  building_id_f%var(:,-1)   = building_id_f%var(:,0)
2050             IF ( nxr == nx )  building_id_f%var(:,nx+1) = building_id_f%var(:,nx)
2051          ENDIF
2052       ENDIF
2053
2054       IF ( building_type_f%from_file )  THEN
2055          var_exchange_int                  = INT( building_type_f%fill, KIND = 4 )
2056          var_exchange_int(nys:nyn,nxl:nxr) =                                  &
2057                          INT( building_type_f%var(nys:nyn,nxl:nxr), KIND = 4 )
2058          CALL exchange_horiz_2d_int( var_exchange_int, nys, nyn, nxl, nxr, nbgp )
2059          DEALLOCATE( building_type_f%var )
2060          ALLOCATE( building_type_f%var(nys-nbgp:nyn+nbgp,nxl-nbgp:nxr+nbgp) )
2061          building_type_f%var = INT( var_exchange_int, KIND = 1 )
2062
2063          IF ( .NOT. bc_ns_cyc )  THEN
2064             IF ( nys == 0  )  building_type_f%var(-1,:)   = building_type_f%var(0,:)
2065             IF ( nyn == ny )  building_type_f%var(ny+1,:) = building_type_f%var(ny,:)
2066          ENDIF
2067          IF ( .NOT. bc_lr_cyc )  THEN
2068             IF ( nxl == 0  )  building_type_f%var(:,-1)   = building_type_f%var(:,0)
2069             IF ( nxr == nx )  building_type_f%var(:,nx+1) = building_type_f%var(:,nx)
2070          ENDIF
2071       ENDIF
2072
2073    END SUBROUTINE netcdf_data_input_topo
2074
2075!------------------------------------------------------------------------------!
2076! Description:
2077! ------------
2078!> Reads initialization data of u, v, w, pt, q, geostrophic wind components,
2079!> as well as soil moisture and soil temperature, derived from larger-scale
2080!> model (COSMO) by Inifor.
2081!------------------------------------------------------------------------------!
2082    SUBROUTINE netcdf_data_input_init_3d
2083
2084       USE arrays_3d,                                                          &
2085           ONLY:  q, pt, u, v, w, zu, zw
2086
2087       USE control_parameters,                                                 &
2088           ONLY:  bc_lr_cyc, bc_ns_cyc, humidity, message_string, neutral
2089
2090       USE indices,                                                            &
2091           ONLY:  nx, nxl, nxlu, nxr, ny, nyn, nys, nysv, nzb, nz, nzt
2092
2093       IMPLICIT NONE
2094
2095       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
2096
2097       LOGICAL      ::  dynamic_3d = .TRUE. !< flag indicating that 3D data is read from dynamic file
2098       
2099       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
2100       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
2101
2102       LOGICAL      ::  check_passed !< flag indicating if a check passed
2103
2104!
2105!--    Skip routine if no input file with dynamic input data is available.
2106       IF ( .NOT. input_pids_dynamic )  RETURN
2107!
2108!--    Please note, Inifor is designed to provide initial data for u and v for
2109!--    the prognostic grid points in case of lateral Dirichlet conditions.
2110!--    This means that Inifor provides data from nxlu:nxr (for u) and
2111!--    from nysv:nyn (for v) at the left and south domain boundary, respectively.
2112!--    However, as work-around for the moment, PALM will run with cyclic
2113!--    conditions and will be initialized with data provided by Inifor
2114!--    boundaries in case of Dirichlet.
2115!--    Hence, simply set set nxlu/nysv to 1 (will be reset to its original value
2116!--    at the end of this routine.
2117       IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = 1
2118       IF ( bc_ns_cyc  .AND.  nys == 0 )  nysv = 1
2119
2120!
2121!--    CPU measurement
2122       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'start' )
2123
2124#if defined ( __netcdf )
2125!
2126!--    Open file in read-only mode
2127       CALL open_read_file( TRIM( input_file_dynamic ) //                      &
2128                            TRIM( coupling_char ), id_dynamic )
2129
2130!
2131!--    At first, inquire all variable names.
2132       CALL inquire_num_variables( id_dynamic, num_vars )
2133!
2134!--    Allocate memory to store variable names.
2135       ALLOCATE( var_names(1:num_vars) )
2136       CALL inquire_variable_names( id_dynamic, var_names )
2137!
2138!--    Read vertical dimension of scalar und w grid.
2139       CALL get_dimension_length( id_dynamic, init_3d%nzu, 'z'     )
2140       CALL get_dimension_length( id_dynamic, init_3d%nzw, 'zw'    )
2141!
2142!--    Read also the horizontal dimensions. These are used just used fo
2143!--    checking the compatibility with the PALM grid before reading.
2144       CALL get_dimension_length( id_dynamic, init_3d%nx,  'x'  )
2145       CALL get_dimension_length( id_dynamic, init_3d%nxu, 'xu' )
2146       CALL get_dimension_length( id_dynamic, init_3d%ny,  'y'  )
2147       CALL get_dimension_length( id_dynamic, init_3d%nyv, 'yv' )
2148
2149!
2150!--    Check for correct horizontal and vertical dimension. Please note,
2151!--    checks are performed directly here and not called from
2152!--    check_parameters as some varialbes are still not allocated there.
2153!--    Moreover, please note, u- and v-grid has 1 grid point less on
2154!--    Inifor grid.
2155       IF ( init_3d%nx-1 /= nx  .OR.  init_3d%nxu-1 /= nx - 1  .OR.            &
2156            init_3d%ny-1 /= ny  .OR.  init_3d%nyv-1 /= ny - 1 )  THEN
2157          message_string = 'Number of inifor horizontal grid points  '//       &
2158                           'does not match the number of numeric grid '//      &
2159                           'points.'
2160          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
2161       ENDIF
2162
2163       IF ( init_3d%nzu /= nz )  THEN
2164          message_string = 'Number of inifor vertical grid points ' //         &
2165                           'does not match the number of numeric grid '//      &
2166                           'points.'
2167          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
2168       ENDIF
2169!
2170!--    Read vertical dimensions. Later, these are required for eventual
2171!--    inter- and extrapolations of the initialization data.
2172       IF ( check_existence( var_names, 'z' ) )  THEN
2173          ALLOCATE( init_3d%zu_atmos(1:init_3d%nzu) )
2174          CALL get_variable( id_dynamic, 'z', init_3d%zu_atmos )
2175       ENDIF
2176       IF ( check_existence( var_names, 'zw' ) )  THEN
2177          ALLOCATE( init_3d%zw_atmos(1:init_3d%nzw) )
2178          CALL get_variable( id_dynamic, 'zw', init_3d%zw_atmos )
2179       ENDIF
2180!
2181!--    Check for consistency between vertical coordinates in dynamic
2182!--    driver and numeric grid.
2183!--    Please note, depending on compiler options both may be
2184!--    equal up to a certain threshold, and differences between
2185!--    the numeric grid and vertical coordinate in the driver can built-
2186!--    up to 10E-1-10E-0 m. For this reason, the check is performed not
2187!--    for exactly matching values.
2188       IF ( ANY( ABS( zu(1:nzt)   - init_3d%zu_atmos(1:init_3d%nzu) )    &
2189                      > 10E-1 )  .OR.                                    &
2190            ANY( ABS( zw(1:nzt-1) - init_3d%zw_atmos(1:init_3d%nzw) )    &
2191                      > 10E-1 ) )  THEN
2192          message_string = 'Vertical grid in dynamic driver does not '// &
2193                           'match the numeric grid.'
2194          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
2195       ENDIF
2196!
2197!--    Read initial geostrophic wind components at
2198!--    t = 0 (index 1 in file).
2199       IF ( check_existence( var_names, 'ls_forcing_ug' ) )  THEN
2200          ALLOCATE( init_3d%ug_init(nzb:nzt+1) )
2201          init_3d%ug_init = 0.0_wp
2202
2203          CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', 1,          &
2204                                init_3d%ug_init(1:nzt) )
2205!
2206!--       Set top-boundary condition (Neumann)
2207          init_3d%ug_init(nzt+1) = init_3d%ug_init(nzt)
2208
2209          init_3d%from_file_ug = .TRUE.
2210       ELSE
2211          init_3d%from_file_ug = .FALSE.
2212       ENDIF
2213       IF ( check_existence( var_names, 'ls_forcing_vg' ) )  THEN
2214          ALLOCATE( init_3d%vg_init(nzb:nzt+1) )
2215          init_3d%vg_init = 0.0_wp
2216
2217          CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', 1,          &
2218                                init_3d%vg_init(1:nzt) )
2219!
2220!--       Set top-boundary condition (Neumann)
2221          init_3d%vg_init(nzt+1) = init_3d%vg_init(nzt)
2222
2223          init_3d%from_file_vg = .TRUE.
2224       ELSE
2225          init_3d%from_file_vg = .FALSE.
2226       ENDIF
2227!
2228!--    Read inital 3D data of u, v, w, pt and q,
2229!--    derived from COSMO model. Read PE-wise yz-slices.
2230!--    Please note, the u-, v- and w-component are defined on different
2231!--    grids with one element less in the x-, y-,
2232!--    and z-direction, respectively. Hence, reading is subdivided
2233!--    into separate loops. 
2234!--    Read u-component
2235       IF ( check_existence( var_names, 'init_atmosphere_u' ) )  THEN
2236!
2237!--       Read attributes for the fill value and level-of-detail
2238          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_u,           &
2239                              .FALSE., 'init_atmosphere_u' )
2240          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_u,             &
2241                              .FALSE., 'init_atmosphere_u' )
2242!
2243!--       level-of-detail 1 - read initialization profile
2244          IF ( init_3d%lod_u == 1 )  THEN
2245             ALLOCATE( init_3d%u_init(nzb:nzt+1) )
2246             init_3d%u_init = 0.0_wp
2247
2248             CALL get_variable( id_dynamic, 'init_atmosphere_u',               &
2249                                init_3d%u_init(nzb+1:nzt) )
2250!
2251!--          Set top-boundary condition (Neumann)
2252             init_3d%u_init(nzt+1) = init_3d%u_init(nzt)
2253!
2254!--       level-of-detail 2 - read 3D initialization data
2255          ELSEIF ( init_3d%lod_u == 2 )  THEN
2256             CALL get_variable( id_dynamic, 'init_atmosphere_u',               &
2257                                u(nzb+1:nzt,nys:nyn,nxlu:nxr),                 &
2258                                nxlu, nys+1, nzb+1,                            &
2259                                nxr-nxlu+1, nyn-nys+1, init_3d%nzu,            &
2260                                dynamic_3d )
2261!
2262!--          Set value at leftmost model grid point nxl = 0. This is because
2263!--          Inifor provides data only from 1:nx-1 since it assumes non-cyclic
2264!--          conditions.
2265             IF ( nxl == 0 )                                                   &
2266                u(nzb+1:nzt,nys:nyn,nxl) = u(nzb+1:nzt,nys:nyn,nxlu)
2267!
2268!--          Set bottom and top-boundary
2269             u(nzb,:,:)   = u(nzb+1,:,:)
2270             u(nzt+1,:,:) = u(nzt,:,:)
2271             
2272          ENDIF
2273          init_3d%from_file_u = .TRUE.
2274       ELSE
2275          message_string = 'Missing initial data for u-component'
2276          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
2277       ENDIF
2278!
2279!--    Read v-component
2280       IF ( check_existence( var_names, 'init_atmosphere_v' ) )  THEN
2281!
2282!--       Read attributes for the fill value and level-of-detail
2283          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_v,           &
2284                              .FALSE., 'init_atmosphere_v' )
2285          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_v,             &
2286                              .FALSE., 'init_atmosphere_v' )
2287!
2288!--       level-of-detail 1 - read initialization profile
2289          IF ( init_3d%lod_v == 1 )  THEN
2290             ALLOCATE( init_3d%v_init(nzb:nzt+1) )
2291             init_3d%v_init = 0.0_wp
2292
2293             CALL get_variable( id_dynamic, 'init_atmosphere_v',               &
2294                                init_3d%v_init(nzb+1:nzt) )
2295!
2296!--          Set top-boundary condition (Neumann)
2297             init_3d%v_init(nzt+1) = init_3d%v_init(nzt)
2298!
2299!--       level-of-detail 2 - read 3D initialization data
2300          ELSEIF ( init_3d%lod_v == 2 )  THEN
2301         
2302             CALL get_variable( id_dynamic, 'init_atmosphere_v',               &
2303                                v(nzb+1:nzt,nysv:nyn,nxl:nxr),                 &
2304                                nxl+1, nysv, nzb+1,                            &
2305                                nxr-nxl+1, nyn-nysv+1, init_3d%nzu,            &
2306                                dynamic_3d )
2307!
2308!--          Set value at southmost model grid point nys = 0. This is because
2309!--          Inifor provides data only from 1:ny-1 since it assumes non-cyclic
2310!--          conditions.
2311             IF ( nys == 0 )                                                   &
2312                v(nzb+1:nzt,nys,nxl:nxr) = v(nzb+1:nzt,nysv,nxl:nxr)                               
2313!
2314!--          Set bottom and top-boundary
2315             v(nzb,:,:)   = v(nzb+1,:,:)
2316             v(nzt+1,:,:) = v(nzt,:,:)
2317             
2318          ENDIF
2319          init_3d%from_file_v = .TRUE.
2320       ELSE
2321          message_string = 'Missing initial data for v-component'
2322          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
2323       ENDIF
2324!
2325!--    Read w-component
2326       IF ( check_existence( var_names, 'init_atmosphere_w' ) )  THEN
2327!
2328!--       Read attributes for the fill value and level-of-detail
2329          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_w,           &
2330                              .FALSE., 'init_atmosphere_w' )
2331          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_w,             &
2332                              .FALSE., 'init_atmosphere_w' )
2333!
2334!--       level-of-detail 1 - read initialization profile
2335          IF ( init_3d%lod_w == 1 )  THEN
2336             ALLOCATE( init_3d%w_init(nzb:nzt+1) )
2337             init_3d%w_init = 0.0_wp
2338
2339             CALL get_variable( id_dynamic, 'init_atmosphere_w',               &
2340                                init_3d%w_init(nzb+1:nzt-1) )
2341!
2342!--          Set top-boundary condition (Neumann)
2343             init_3d%w_init(nzt:nzt+1) = init_3d%w_init(nzt-1)
2344!
2345!--       level-of-detail 2 - read 3D initialization data
2346          ELSEIF ( init_3d%lod_w == 2 )  THEN
2347
2348             CALL get_variable( id_dynamic, 'init_atmosphere_w',                &
2349                                w(nzb+1:nzt-1,nys:nyn,nxl:nxr),                 &
2350                                nxl+1, nys+1, nzb+1,                            &
2351                                nxr-nxl+1, nyn-nys+1, init_3d%nzw,              &
2352                                dynamic_3d )
2353!
2354!--          Set bottom and top-boundary                               
2355             w(nzb,:,:)   = 0.0_wp 
2356             w(nzt,:,:)   = w(nzt-1,:,:)
2357             w(nzt+1,:,:) = w(nzt-1,:,:)
2358
2359          ENDIF
2360          init_3d%from_file_w = .TRUE.
2361       ELSE
2362          message_string = 'Missing initial data for w-component'
2363          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
2364       ENDIF
2365!
2366!--    Read potential temperature
2367       IF ( .NOT. neutral )  THEN
2368          IF ( check_existence( var_names, 'init_atmosphere_pt' ) )  THEN
2369!
2370!--          Read attributes for the fill value and level-of-detail
2371             CALL get_attribute( id_dynamic, char_fill, init_3d%fill_pt,       &
2372                                 .FALSE., 'init_atmosphere_pt' )
2373             CALL get_attribute( id_dynamic, char_lod, init_3d%lod_pt,         &
2374                                 .FALSE., 'init_atmosphere_pt' )
2375!
2376!--          level-of-detail 1 - read initialization profile
2377             IF ( init_3d%lod_pt == 1 )  THEN
2378                ALLOCATE( init_3d%pt_init(nzb:nzt+1) )
2379
2380                CALL get_variable( id_dynamic, 'init_atmosphere_pt',           &
2381                                   init_3d%pt_init(nzb+1:nzt) )
2382!
2383!--             Set Neumann top and surface boundary condition for initial
2384!--             profil
2385                init_3d%pt_init(nzb)   = init_3d%pt_init(nzb+1)
2386                init_3d%pt_init(nzt+1) = init_3d%pt_init(nzt)
2387!
2388!--          level-of-detail 2 - read 3D initialization data
2389             ELSEIF ( init_3d%lod_pt == 2 )  THEN
2390
2391                CALL get_variable( id_dynamic, 'init_atmosphere_pt',           &
2392                                   pt(nzb+1:nzt,nys:nyn,nxl:nxr),              &
2393                                   nxl+1, nys+1, nzb+1,                        &
2394                                   nxr-nxl+1, nyn-nys+1, init_3d%nzu,          &
2395                                   dynamic_3d )
2396                                   
2397!
2398!--             Set bottom and top-boundary
2399                pt(nzb,:,:)   = pt(nzb+1,:,:)
2400                pt(nzt+1,:,:) = pt(nzt,:,:)             
2401
2402             ENDIF
2403             init_3d%from_file_pt = .TRUE.
2404          ELSE
2405             message_string = 'Missing initial data for ' //                   &
2406                              'potential temperature'
2407             CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
2408          ENDIF
2409       ENDIF
2410!
2411!--    Read mixing ratio
2412       IF ( humidity )  THEN
2413          IF ( check_existence( var_names, 'init_atmosphere_qv' ) )  THEN
2414!
2415!--          Read attributes for the fill value and level-of-detail
2416             CALL get_attribute( id_dynamic, char_fill, init_3d%fill_q,        &
2417                                 .FALSE., 'init_atmosphere_qv' )
2418             CALL get_attribute( id_dynamic, char_lod, init_3d%lod_q,          &
2419                                 .FALSE., 'init_atmosphere_qv' )
2420!
2421!--          level-of-detail 1 - read initialization profile
2422             IF ( init_3d%lod_q == 1 )  THEN
2423                ALLOCATE( init_3d%q_init(nzb:nzt+1) )
2424
2425                CALL get_variable( id_dynamic, 'init_atmosphere_qv',           &
2426                                    init_3d%q_init(nzb+1:nzt) )
2427!
2428!--             Set bottom and top boundary condition (Neumann)
2429                init_3d%q_init(nzb)   = init_3d%q_init(nzb+1)
2430                init_3d%q_init(nzt+1) = init_3d%q_init(nzt)
2431!
2432!--          level-of-detail 2 - read 3D initialization data
2433             ELSEIF ( init_3d%lod_q == 2 )  THEN
2434             
2435                CALL get_variable( id_dynamic, 'init_atmosphere_qv',           &
2436                                   q(nzb+1:nzt,nys:nyn,nxl:nxr),               &
2437                                   nxl+1, nys+1, nzb+1,                        &
2438                                   nxr-nxl+1, nyn-nys+1, init_3d%nzu,          &
2439                                   dynamic_3d )
2440                                   
2441!
2442!--             Set bottom and top-boundary
2443                q(nzb,:,:)   = q(nzb+1,:,:)
2444                q(nzt+1,:,:) = q(nzt,:,:)
2445               
2446             ENDIF
2447             init_3d%from_file_q = .TRUE.
2448          ELSE
2449             message_string = 'Missing initial data for ' //                   &
2450                              'mixing ratio'
2451             CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
2452          ENDIF
2453       ENDIF
2454!
2455!--    Close input file
2456       CALL close_input_file( id_dynamic )
2457#endif
2458!
2459!--    End of CPU measurement
2460       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'stop' )
2461!
2462!--    Finally, check if the input data has any fill values. Please note,
2463!--    checks depend on the LOD of the input data.
2464       IF ( init_3d%from_file_u )  THEN
2465          check_passed = .TRUE.
2466          IF ( init_3d%lod_u == 1 )  THEN
2467             IF ( ANY( init_3d%u_init(nzb+1:nzt+1) == init_3d%fill_u ) )       &
2468                check_passed = .FALSE.
2469          ELSEIF ( init_3d%lod_u == 2 )  THEN
2470             IF ( ANY( u(nzb+1:nzt+1,nys:nyn,nxlu:nxr) == init_3d%fill_u ) )   &
2471                check_passed = .FALSE.
2472          ENDIF
2473          IF ( .NOT. check_passed )  THEN
2474             message_string = 'NetCDF input for init_atmosphere_u must ' //    &
2475                              'not contain any _FillValues'
2476             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
2477          ENDIF
2478       ENDIF
2479
2480       IF ( init_3d%from_file_v )  THEN
2481          check_passed = .TRUE.
2482          IF ( init_3d%lod_v == 1 )  THEN
2483             IF ( ANY( init_3d%v_init(nzb+1:nzt+1) == init_3d%fill_v ) )       &
2484                check_passed = .FALSE.
2485          ELSEIF ( init_3d%lod_v == 2 )  THEN
2486             IF ( ANY( v(nzb+1:nzt+1,nysv:nyn,nxl:nxr) == init_3d%fill_v ) )   &
2487                check_passed = .FALSE.
2488          ENDIF
2489          IF ( .NOT. check_passed )  THEN
2490             message_string = 'NetCDF input for init_atmosphere_v must ' //    &
2491                              'not contain any _FillValues'
2492             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
2493          ENDIF
2494       ENDIF
2495
2496       IF ( init_3d%from_file_w )  THEN
2497          check_passed = .TRUE.
2498          IF ( init_3d%lod_w == 1 )  THEN
2499             IF ( ANY( init_3d%w_init(nzb+1:nzt) == init_3d%fill_w ) )         &
2500                check_passed = .FALSE.
2501          ELSEIF ( init_3d%lod_w == 2 )  THEN
2502             IF ( ANY( w(nzb+1:nzt,nys:nyn,nxl:nxr) == init_3d%fill_w ) )      &
2503                check_passed = .FALSE.
2504          ENDIF
2505          IF ( .NOT. check_passed )  THEN
2506             message_string = 'NetCDF input for init_atmosphere_w must ' //    &
2507                              'not contain any _FillValues'
2508             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
2509          ENDIF
2510       ENDIF
2511
2512       IF ( init_3d%from_file_pt )  THEN
2513          check_passed = .TRUE.
2514          IF ( init_3d%lod_pt == 1 )  THEN
2515             IF ( ANY( init_3d%pt_init(nzb+1:nzt+1) == init_3d%fill_pt ) )     &
2516                check_passed = .FALSE.
2517          ELSEIF ( init_3d%lod_pt == 2 )  THEN
2518             IF ( ANY( pt(nzb+1:nzt+1,nys:nyn,nxl:nxr) == init_3d%fill_pt ) )  &
2519                check_passed = .FALSE.
2520          ENDIF
2521          IF ( .NOT. check_passed )  THEN
2522             message_string = 'NetCDF input for init_atmosphere_pt must ' //   &
2523                              'not contain any _FillValues'
2524             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
2525          ENDIF
2526       ENDIF
2527
2528       IF ( init_3d%from_file_q )  THEN
2529          check_passed = .TRUE.
2530          IF ( init_3d%lod_q == 1 )  THEN
2531             IF ( ANY( init_3d%q_init(nzb+1:nzt+1) == init_3d%fill_q ) )       &
2532                check_passed = .FALSE.
2533          ELSEIF ( init_3d%lod_q == 2 )  THEN
2534             IF ( ANY( q(nzb+1:nzt+1,nys:nyn,nxl:nxr) == init_3d%fill_q ) )    &
2535                check_passed = .FALSE.
2536          ENDIF
2537          IF ( .NOT. check_passed )  THEN
2538             message_string = 'NetCDF input for init_atmosphere_q must ' //    &
2539                              'not contain any _FillValues'
2540             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
2541          ENDIF
2542       ENDIF
2543!
2544!--    Workaround for cyclic conditions. Please see above for further explanation.
2545       IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = nxl
2546       IF ( bc_ns_cyc  .AND.  nys == 0 )  nysv = nys
2547
2548    END SUBROUTINE netcdf_data_input_init_3d
2549   
2550!------------------------------------------------------------------------------!
2551! Description:
2552! ------------
2553!> Reads initialization data of u, v, w, pt, q, geostrophic wind components,
2554!> as well as soil moisture and soil temperature, derived from larger-scale
2555!> model (COSMO) by Inifor.
2556!------------------------------------------------------------------------------!
2557    SUBROUTINE netcdf_data_input_init_lsm
2558
2559       USE control_parameters,                                                 &
2560           ONLY:  message_string
2561
2562       USE indices,                                                            &
2563           ONLY:  nx, nxl, nxr, ny, nyn, nys
2564
2565       IMPLICIT NONE
2566
2567       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
2568     
2569       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
2570       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
2571
2572!
2573!--    Skip routine if no input file with dynamic input data is available.
2574       IF ( .NOT. input_pids_dynamic )  RETURN
2575!
2576!--    CPU measurement
2577       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'start' )
2578
2579#if defined ( __netcdf )
2580!
2581!--    Open file in read-only mode
2582       CALL open_read_file( TRIM( input_file_dynamic ) //                      &
2583                            TRIM( coupling_char ), id_dynamic )
2584
2585!
2586!--    At first, inquire all variable names.
2587       CALL inquire_num_variables( id_dynamic, num_vars )
2588!
2589!--    Allocate memory to store variable names.
2590       ALLOCATE( var_names(1:num_vars) )
2591       CALL inquire_variable_names( id_dynamic, var_names )
2592!
2593!--    Read vertical dimension for soil depth.
2594       IF ( check_existence( var_names, 'zsoil' ) )                            &
2595          CALL get_dimension_length( id_dynamic, init_3d%nzs, 'zsoil' )
2596!
2597!--    Read also the horizontal dimensions required for soil initialization.
2598!--    Please note, in case of non-nested runs or in case of root domain,
2599!--    these data is already available, but will be read again for the sake
2600!--    of clearness.
2601       CALL get_dimension_length( id_dynamic, init_3d%nx,  'x'  )
2602       CALL get_dimension_length( id_dynamic, init_3d%ny,  'y'  )
2603!
2604!--    Check for correct horizontal and vertical dimension. Please note,
2605!--    in case of non-nested runs or in case of root domain, these checks
2606!--    are already performed
2607       IF ( init_3d%nx-1 /= nx  .OR.  init_3d%ny-1 /= ny )  THEN
2608          message_string = 'Number of inifor horizontal grid points  '//       &
2609                           'does not match the number of numeric grid points.'
2610          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
2611       ENDIF
2612!
2613!--    Read vertical dimensions. Later, these are required for eventual
2614!--    inter- and extrapolations of the initialization data.
2615       IF ( check_existence( var_names, 'zsoil' ) )  THEN
2616          ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )
2617          CALL get_variable( id_dynamic, 'zsoil', init_3d%z_soil )
2618       ENDIF
2619!
2620!--    Read initial data for soil moisture
2621       IF ( check_existence( var_names, 'init_soil_m' ) )  THEN
2622!
2623!--       Read attributes for the fill value and level-of-detail
2624          CALL get_attribute( id_dynamic, char_fill,                           &
2625                              init_3d%fill_msoil,                              &
2626                              .FALSE., 'init_soil_m' )
2627          CALL get_attribute( id_dynamic, char_lod,                            &
2628                              init_3d%lod_msoil,                               &
2629                              .FALSE., 'init_soil_m' )
2630!
2631!--       level-of-detail 1 - read initialization profile
2632          IF ( init_3d%lod_msoil == 1 )  THEN
2633             ALLOCATE( init_3d%msoil_1d(0:init_3d%nzs-1) )
2634
2635             CALL get_variable( id_dynamic, 'init_soil_m',                     &
2636                                init_3d%msoil_1d(0:init_3d%nzs-1) )
2637!
2638!--       level-of-detail 2 - read 3D initialization data
2639          ELSEIF ( init_3d%lod_msoil == 2 )  THEN
2640             ALLOCATE ( init_3d%msoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
2641
2642            CALL get_variable( id_dynamic, 'init_soil_m',                      &   
2643                             init_3d%msoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
2644                             nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
2645
2646          ENDIF
2647          init_3d%from_file_msoil = .TRUE.
2648       ENDIF
2649!
2650!--    Read soil temperature
2651       IF ( check_existence( var_names, 'init_soil_t' ) )  THEN
2652!
2653!--       Read attributes for the fill value and level-of-detail
2654          CALL get_attribute( id_dynamic, char_fill,                           &
2655                              init_3d%fill_tsoil,                              &
2656                              .FALSE., 'init_soil_t' )
2657          CALL get_attribute( id_dynamic, char_lod,                            &
2658                              init_3d%lod_tsoil,                               &
2659                              .FALSE., 'init_soil_t' )
2660!
2661!--       level-of-detail 1 - read initialization profile
2662          IF ( init_3d%lod_tsoil == 1 )  THEN
2663             ALLOCATE( init_3d%tsoil_1d(0:init_3d%nzs-1) )
2664
2665             CALL get_variable( id_dynamic, 'init_soil_t',                     &
2666                                init_3d%tsoil_1d(0:init_3d%nzs-1) )
2667
2668!
2669!--       level-of-detail 2 - read 3D initialization data
2670          ELSEIF ( init_3d%lod_tsoil == 2 )  THEN
2671             ALLOCATE ( init_3d%tsoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
2672             
2673             CALL get_variable( id_dynamic, 'init_soil_t',                     &   
2674                             init_3d%tsoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
2675                             nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
2676          ENDIF
2677          init_3d%from_file_tsoil = .TRUE.
2678       ENDIF
2679!
2680!--    Close input file
2681       CALL close_input_file( id_dynamic )
2682#endif
2683!
2684!--    End of CPU measurement
2685       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'stop' )
2686
2687    END SUBROUTINE netcdf_data_input_init_lsm   
2688
2689!------------------------------------------------------------------------------!
2690! Description:
2691! ------------
2692!> Reads data at lateral and top boundaries derived from larger-scale model
2693!> (COSMO) by Inifor.
2694!------------------------------------------------------------------------------!
2695    SUBROUTINE netcdf_data_input_lsf
2696
2697       USE control_parameters,                                                 &
2698           ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,              &
2699                  bc_dirichlet_s, bc_lr_cyc, bc_ns_cyc, humidity,              &
2700                  neutral, nesting_offline, time_since_reference_point
2701
2702       USE indices,                                                            &
2703           ONLY:  nxl, nxlu, nxr, nyn, nys, nysv, nzb, nzt
2704
2705       IMPLICIT NONE
2706       
2707       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
2708       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
2709       INTEGER(iwp) ::  t          !< running index time dimension
2710
2711       nest_offl%from_file = MERGE( .TRUE., .FALSE., input_pids_dynamic ) 
2712!
2713!--    Skip input if no forcing from larger-scale models is applied.
2714       IF ( .NOT. nesting_offline )  RETURN
2715
2716!
2717!--    CPU measurement
2718       CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'start' )
2719
2720#if defined ( __netcdf )
2721!
2722!--    Open file in read-only mode
2723       CALL open_read_file( TRIM( input_file_dynamic ) //                      &
2724                            TRIM( coupling_char ), id_dynamic )
2725!
2726!--    Initialize INIFOR forcing.
2727       IF ( .NOT. nest_offl%init )  THEN
2728!
2729!--       At first, inquire all variable names.
2730          CALL inquire_num_variables( id_dynamic, num_vars )
2731!
2732!--       Allocate memory to store variable names.
2733          ALLOCATE( nest_offl%var_names(1:num_vars) )
2734          CALL inquire_variable_names( id_dynamic, nest_offl%var_names )
2735!
2736!--       Read time dimension, allocate memory and finally read time array
2737          CALL get_dimension_length( id_dynamic, nest_offl%nt, 'time' )
2738
2739          IF ( check_existence( nest_offl%var_names, 'time' ) )  THEN
2740             ALLOCATE( nest_offl%time(0:nest_offl%nt-1) )
2741             CALL get_variable( id_dynamic, 'time', nest_offl%time )
2742          ENDIF
2743!
2744!--       Read vertical dimension of scalar und w grid
2745          CALL get_dimension_length( id_dynamic, nest_offl%nzu, 'z' )
2746          CALL get_dimension_length( id_dynamic, nest_offl%nzw, 'zw' )
2747
2748          IF ( check_existence( nest_offl%var_names, 'z' ) )  THEN
2749             ALLOCATE( nest_offl%zu_atmos(1:nest_offl%nzu) )
2750             CALL get_variable( id_dynamic, 'z', nest_offl%zu_atmos )
2751          ENDIF
2752          IF ( check_existence( nest_offl%var_names, 'zw' ) )  THEN
2753             ALLOCATE( nest_offl%zw_atmos(1:nest_offl%nzw) )
2754             CALL get_variable( id_dynamic, 'zw', nest_offl%zw_atmos )
2755          ENDIF
2756
2757!
2758!--       Read surface pressure
2759          IF ( check_existence( nest_offl%var_names,                           &
2760                                'surface_forcing_surface_pressure' ) )  THEN
2761             ALLOCATE( nest_offl%surface_pressure(0:nest_offl%nt-1) )
2762             CALL get_variable( id_dynamic,                                    &
2763                                'surface_forcing_surface_pressure',            &
2764                                nest_offl%surface_pressure )
2765          ENDIF
2766!
2767!--       Set control flag to indicate that initialization is already done
2768          nest_offl%init = .TRUE.
2769
2770       ENDIF
2771
2772!
2773!--    Obtain time index for current input starting at 0.
2774!--    @todo: At the moment time, in INIFOR and simulated time correspond
2775!--           to each other. If required, adjust to daytime.
2776       nest_offl%tind = MINLOC( ABS( nest_offl%time -                          &
2777                                     time_since_reference_point ), DIM = 1 )   &
2778                        - 1
2779       nest_offl%tind_p = nest_offl%tind + 1       
2780!
2781!--    Read geostrophic wind components. In case of forcing, this is only
2782!--    required if cyclic boundary conditions are applied.
2783       IF ( bc_lr_cyc  .AND.  bc_ns_cyc )  THEN
2784          DO  t = nest_offl%tind, nest_offl%tind_p
2785!              CALL get_variable_pr( id_dynamic, 'tend_ug', t+1,           &
2786!                                    nest_offl%ug(t-nest_offl%tind,:) )
2787!              CALL get_variable_pr( id_dynamic, 'tend_vg', t+1,           &
2788!                                    nest_offl%ug(t-nest_offl%tind,:) )
2789             CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', t+1,           &
2790                                   nest_offl%ug(t-nest_offl%tind,:) )
2791             CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', t+1,           &
2792                                   nest_offl%ug(t-nest_offl%tind,:) )
2793          ENDDO
2794       ENDIF
2795!
2796!--    Read data at lateral and top boundaries. Please note, at left and
2797!--    right domain boundary, yz-layers are read for u, v, w, pt and q.
2798!--    For the v-component, the data starts at nysv, while for the other
2799!--    quantities the data starts at nys. This is equivalent at the north
2800!--    and south domain boundary for the u-component.
2801!--    Further, lateral data is not accessed by parallel IO, indicated by the
2802!--    last passed flag in the subroutine get_variable(). This is because
2803!--    not every PE participates in this collective blocking read operation.
2804       IF ( bc_dirichlet_l )  THEN
2805          CALL get_variable( id_dynamic, 'ls_forcing_left_u',                  &
2806                           nest_offl%u_left(0:1,nzb+1:nzt,nys:nyn),            &
2807                           nys+1, nzb+1, nest_offl%tind+1,                     &
2808                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
2809     
2810          CALL get_variable( id_dynamic, 'ls_forcing_left_v',                  &
2811                           nest_offl%v_left(0:1,nzb+1:nzt,nysv:nyn),           &
2812                           nysv, nzb+1, nest_offl%tind+1,                      &
2813                           nyn-nysv+1, nest_offl%nzu, 2, .FALSE. )
2814
2815          CALL get_variable( id_dynamic, 'ls_forcing_left_w',                  &
2816                           nest_offl%w_left(0:1,nzb+1:nzt-1,nys:nyn),          &
2817                           nys+1, nzb+1, nest_offl%tind+1,                     &
2818                           nyn-nys+1, nest_offl%nzw, 2, .FALSE. )
2819
2820          IF ( .NOT. neutral )  THEN
2821             CALL get_variable( id_dynamic, 'ls_forcing_left_pt',              &
2822                           nest_offl%pt_left(0:1,nzb+1:nzt,nys:nyn),           &
2823                           nys+1, nzb+1, nest_offl%tind+1,                     &
2824                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
2825          ENDIF
2826
2827          IF ( humidity )  THEN
2828             CALL get_variable( id_dynamic, 'ls_forcing_left_qv',              &
2829                           nest_offl%q_left(0:1,nzb+1:nzt,nys:nyn),            &
2830                           nys+1, nzb+1, nest_offl%tind+1,                     &
2831                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
2832          ENDIF
2833
2834       ENDIF
2835
2836       IF ( bc_dirichlet_r )  THEN
2837          CALL get_variable( id_dynamic, 'ls_forcing_right_u',                 &
2838                           nest_offl%u_right(0:1,nzb+1:nzt,nys:nyn),           &
2839                           nys+1, nzb+1, nest_offl%tind+1,                     &
2840                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
2841                           
2842          CALL get_variable( id_dynamic, 'ls_forcing_right_v',                 &
2843                           nest_offl%v_right(0:1,nzb+1:nzt,nysv:nyn),          &
2844                           nysv, nzb+1, nest_offl%tind+1,                      &
2845                           nyn-nysv+1, nest_offl%nzu, 2, .FALSE. )
2846                           
2847          CALL get_variable( id_dynamic, 'ls_forcing_right_w',                 &
2848                           nest_offl%w_right(0:1,nzb+1:nzt-1,nys:nyn),         &
2849                           nys+1, nzb+1, nest_offl%tind+1,                     &
2850                           nyn-nys+1, nest_offl%nzw, 2, .FALSE. )
2851                           
2852          IF ( .NOT. neutral )  THEN
2853             CALL get_variable( id_dynamic, 'ls_forcing_right_pt',             &
2854                           nest_offl%pt_right(0:1,nzb+1:nzt,nys:nyn),          &
2855                           nys+1, nzb+1, nest_offl%tind+1,                     &
2856                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
2857          ENDIF
2858          IF ( humidity )  THEN
2859             CALL get_variable( id_dynamic, 'ls_forcing_right_qv',             &
2860                           nest_offl%q_right(0:1,nzb+1:nzt,nys:nyn),           &
2861                           nys+1, nzb+1, nest_offl%tind+1,                     &
2862                           nyn-nys+1, nest_offl%nzu, 2, .FALSE. )
2863          ENDIF
2864       ENDIF
2865
2866       IF ( bc_dirichlet_n )  THEN
2867       
2868          CALL get_variable( id_dynamic, 'ls_forcing_north_u',                 &
2869                           nest_offl%u_north(0:1,nzb+1:nzt,nxlu:nxr),          &
2870                           nxlu, nzb+1, nest_offl%tind+1,                      &
2871                           nxr-nxlu+1, nest_offl%nzu, 2, .FALSE. )
2872                           
2873          CALL get_variable( id_dynamic, 'ls_forcing_north_v',                 &
2874                           nest_offl%v_north(0:1,nzb+1:nzt,nxl:nxr),           &
2875                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2876                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
2877                           
2878          CALL get_variable( id_dynamic, 'ls_forcing_north_w',                 &
2879                           nest_offl%w_north(0:1,nzb+1:nzt-1,nxl:nxr),         &
2880                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2881                           nxr-nxl+1, nest_offl%nzw, 2, .FALSE. )
2882                           
2883          IF ( .NOT. neutral )  THEN
2884             CALL get_variable( id_dynamic, 'ls_forcing_north_pt',             &
2885                           nest_offl%pt_north(0:1,nzb+1:nzt,nxl:nxr),          &
2886                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2887                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
2888          ENDIF
2889          IF ( humidity )  THEN
2890             CALL get_variable( id_dynamic, 'ls_forcing_north_qv',             &
2891                           nest_offl%q_north(0:1,nzb+1:nzt,nxl:nxr),           &
2892                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2893                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
2894          ENDIF
2895       ENDIF
2896
2897       IF ( bc_dirichlet_s )  THEN
2898          CALL get_variable( id_dynamic, 'ls_forcing_south_u',                 &
2899                           nest_offl%u_south(0:1,nzb+1:nzt,nxlu:nxr),          &
2900                           nxlu, nzb+1, nest_offl%tind+1,                      &
2901                           nxr-nxlu+1, nest_offl%nzu, 2, .FALSE. )
2902
2903          CALL get_variable( id_dynamic, 'ls_forcing_south_v',                 &
2904                           nest_offl%v_south(0:1,nzb+1:nzt,nxl:nxr),           &
2905                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2906                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
2907                           
2908          CALL get_variable( id_dynamic, 'ls_forcing_south_w',                 &
2909                           nest_offl%w_south(0:1,nzb+1:nzt-1,nxl:nxr),         &
2910                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2911                           nxr-nxl+1, nest_offl%nzw, 2, .FALSE. )
2912                           
2913          IF ( .NOT. neutral )  THEN
2914             CALL get_variable( id_dynamic, 'ls_forcing_south_pt',             &
2915                           nest_offl%pt_south(0:1,nzb+1:nzt,nxl:nxr),          &
2916                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2917                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
2918          ENDIF
2919          IF ( humidity )  THEN
2920             CALL get_variable( id_dynamic, 'ls_forcing_south_qv',             &
2921                           nest_offl%q_south(0:1,nzb+1:nzt,nxl:nxr),           &
2922                           nxl+1, nzb+1, nest_offl%tind+1,                     &
2923                           nxr-nxl+1, nest_offl%nzu, 2, .FALSE. )
2924          ENDIF
2925       ENDIF
2926
2927!
2928!--    Top boundary
2929       CALL get_variable( id_dynamic, 'ls_forcing_top_u',                      &
2930                             nest_offl%u_top(0:1,nys:nyn,nxlu:nxr),            &
2931                             nxlu, nys+1, nest_offl%tind+1,                    &
2932                             nxr-nxlu+1, nyn-nys+1, 2, .TRUE. )
2933
2934       CALL get_variable( id_dynamic, 'ls_forcing_top_v',                      &
2935                             nest_offl%v_top(0:1,nysv:nyn,nxl:nxr),            &
2936                             nxl+1, nysv, nest_offl%tind+1,                    &
2937                             nxr-nxl+1, nyn-nysv+1, 2, .TRUE. )
2938                             
2939       CALL get_variable( id_dynamic, 'ls_forcing_top_w',                      &
2940                             nest_offl%w_top(0:1,nys:nyn,nxl:nxr),             &
2941                             nxl+1, nys+1, nest_offl%tind+1,                   &
2942                             nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
2943                             
2944       IF ( .NOT. neutral )  THEN
2945          CALL get_variable( id_dynamic, 'ls_forcing_top_pt',                  &
2946                                nest_offl%pt_top(0:1,nys:nyn,nxl:nxr),         &
2947                                nxl+1, nys+1, nest_offl%tind+1,                &
2948                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
2949       ENDIF
2950       IF ( humidity )  THEN
2951          CALL get_variable( id_dynamic, 'ls_forcing_top_qv',                  &
2952                                nest_offl%q_top(0:1,nys:nyn,nxl:nxr),          &
2953                                nxl+1, nys+1, nest_offl%tind+1,                &
2954                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
2955       ENDIF
2956
2957!
2958!--    Close input file
2959       CALL close_input_file( id_dynamic )
2960#endif
2961!
2962!--    End of CPU measurement
2963       CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'stop' )
2964
2965    END SUBROUTINE netcdf_data_input_lsf
2966
2967
2968!------------------------------------------------------------------------------!
2969! Description:
2970! ------------
2971!> Checks input file for consistency and minimum requirements.
2972!------------------------------------------------------------------------------!
2973    SUBROUTINE netcdf_data_input_check_dynamic
2974
2975       USE control_parameters,                                                 &
2976           ONLY:  initializing_actions, message_string, nesting_offline 
2977
2978       IMPLICIT NONE
2979
2980!
2981!--    In case of forcing, check whether dynamic input file is present
2982       IF ( .NOT. input_pids_dynamic  .AND.  nesting_offline  )  THEN
2983          message_string = 'nesting_offline = .TRUE. requires dynamic '  //    &
2984                            'input file ' //                                   &
2985                            TRIM( input_file_dynamic ) // TRIM( coupling_char )
2986          CALL message( 'netcdf_data_input_mod', 'PA0546', 1, 2, 0, 6, 0 )
2987       ENDIF
2988!
2989!--    Dynamic input file must also be present if initialization via inifor is
2990!--    prescribed.
2991       IF ( .NOT. input_pids_dynamic  .AND.                                    &
2992            TRIM( initializing_actions ) == 'inifor' )  THEN
2993          message_string = 'initializing_actions = inifor requires dynamic ' //&
2994                           'input file ' // TRIM( input_file_dynamic ) //      &
2995                           TRIM( coupling_char )
2996          CALL message( 'netcdf_data_input_mod', 'PA0547', 1, 2, 0, 6, 0 )
2997       ENDIF
2998
2999    END SUBROUTINE netcdf_data_input_check_dynamic
3000
3001!------------------------------------------------------------------------------!
3002! Description:
3003! ------------
3004!> Checks input file for consistency and minimum requirements.
3005!------------------------------------------------------------------------------!
3006    SUBROUTINE netcdf_data_input_check_static
3007
3008       USE arrays_3d,                                                          &
3009           ONLY:  zu
3010
3011       USE control_parameters,                                                 &
3012           ONLY:  land_surface, message_string, urban_surface
3013
3014       USE grid_variables,                                                     &
3015           ONLY:  dx, dy
3016
3017       USE indices,                                                            &
3018           ONLY:  nx, nxl, nxr, ny, nyn, nys
3019
3020       IMPLICIT NONE
3021
3022       INTEGER(iwp) ::  i      !< loop index along x-direction
3023       INTEGER(iwp) ::  j      !< loop index along y-direction
3024       INTEGER(iwp) ::  n_surf !< number of different surface types at given location
3025
3026       LOGICAL      ::  check_passed !< flag indicating if a check passed
3027
3028!
3029!--    Return if no static input file is available
3030       IF ( .NOT. input_pids_static )  RETURN
3031!
3032!--    Check whether dimension size in input file matches the model dimensions
3033       IF ( dim_static%nx-1 /= nx  .OR.  dim_static%ny-1 /= ny )  THEN
3034          message_string = 'Static input file: horizontal dimension in ' //    &
3035                           'x- and/or y-direction ' //                         &
3036                           'do not match the respective model dimension'
3037          CALL message( 'netcdf_data_input_mod', 'PA0548', 1, 2, 0, 6, 0 )
3038       ENDIF
3039!
3040!--    Check if grid spacing of provided input data matches the respective
3041!--    grid spacing in the model.
3042       IF ( ABS( dim_static%x(1) - dim_static%x(0) - dx ) > 10E-6_wp  .OR.     &
3043            ABS( dim_static%y(1) - dim_static%y(0) - dy ) > 10E-6_wp )  THEN
3044          message_string = 'Static input file: horizontal grid spacing ' //    &
3045                           'in x- and/or y-direction ' //                      &
3046                           'do not match the respective model grid spacing.'
3047          CALL message( 'netcdf_data_input_mod', 'PA0549', 1, 2, 0, 6, 0 )
3048       ENDIF
3049!
3050!--    Check for correct dimension of surface_fractions, should run from 0-2.
3051       IF ( surface_fraction_f%from_file )  THEN
3052          IF ( surface_fraction_f%nf-1 > 2 )  THEN
3053             message_string = 'nsurface_fraction must not be larger than 3.' 
3054             CALL message( 'netcdf_data_input_mod', 'PA0580', 1, 2, 0, 6, 0 )
3055          ENDIF
3056       ENDIF
3057!
3058!--    Check orography for fill-values. For the moment, give an error message.
3059!--    More advanced methods, e.g. a nearest neighbor algorithm as used in GIS
3060!--    systems might be implemented later.
3061!--    Please note, if no terrain height is provided, it is set to 0.
3062       IF ( ANY( terrain_height_f%var == terrain_height_f%fill ) )  THEN
3063          message_string = 'NetCDF variable zt is not ' //                     &
3064                           'allowed to have missing data'
3065          CALL message( 'netcdf_data_input_mod', 'PA0550', 2, 2, myid, 6, 0 )
3066       ENDIF
3067!
3068!--    Check for negative terrain heights
3069       IF ( ANY( terrain_height_f%var < 0.0_wp ) )  THEN
3070          message_string = 'NetCDF variable zt is not ' //                     &
3071                           'allowed to have negative values'
3072          CALL message( 'netcdf_data_input_mod', 'PA0551', 2, 2, myid, 6, 0 )
3073       ENDIF
3074!
3075!--    If 3D buildings are read, check if building information is consistent
3076!--    to numeric grid.
3077       IF ( buildings_f%from_file )  THEN
3078          IF ( buildings_f%lod == 2 )  THEN
3079             IF ( buildings_f%nz > SIZE( zu ) )  THEN
3080                message_string = 'Reading 3D building data - too much ' //     &
3081                                 'data points along the vertical coordinate.'
3082                CALL message( 'netcdf_data_input_mod', 'PA0552', 2, 2, 0, 6, 0 )
3083             ENDIF
3084
3085             IF ( ANY( buildings_f%z(0:buildings_f%nz-1) /=                    &
3086                       zu(0:buildings_f%nz-1) ) )  THEN
3087                message_string = 'Reading 3D building data - vertical ' //     &
3088                                 'coordinate do not match numeric grid.'
3089                CALL message( 'netcdf_data_input_mod', 'PA0553', 2, 2, 0, 6, 0 )
3090             ENDIF
3091          ENDIF
3092       ENDIF
3093
3094!
3095!--    Skip further checks concerning buildings and natural surface properties
3096!--    if no urban surface and land surface model are applied.
3097       IF (  .NOT. land_surface  .OR.  .NOT. urban_surface )  RETURN
3098!
3099!--    Check for minimum requirement of surface-classification data in case
3100!--    static input file is used.
3101       IF ( ( .NOT. vegetation_type_f%from_file  .OR.                          &
3102              .NOT. pavement_type_f%from_file    .OR.                          &
3103              .NOT. water_type_f%from_file       .OR.                          &
3104              .NOT. soil_type_f%from_file             ) .OR.                   &
3105             ( urban_surface  .AND.  .NOT. building_type_f%from_file ) )  THEN
3106          message_string = 'Minimum requirement for surface classification ' //&
3107                           'is not fulfilled. At least ' //                    &
3108                           'vegetation_type, pavement_type, ' //               &
3109                           'soil_type and water_type are '//                   &
3110                           'required. If urban-surface model is applied, ' //  &
3111                           'also building_type ist required'
3112          CALL message( 'netcdf_data_input_mod', 'PA0554', 1, 2, 0, 6, 0 )
3113       ENDIF
3114!
3115!--    Check for general availability of input variables.
3116!--    If vegetation_type is 0 at any location, vegetation_pars as well as
3117!--    root_area_dens_s are required.
3118       IF ( vegetation_type_f%from_file )  THEN
3119          IF ( ANY( vegetation_type_f%var == 0 ) )  THEN
3120             IF ( .NOT. vegetation_pars_f%from_file )  THEN
3121                message_string = 'If vegetation_type = 0 at any location, ' // &
3122                                 'vegetation_pars is required'
3123                CALL message( 'netcdf_data_input_mod', 'PA0555', 2, 2, -1, 6, 0 )
3124             ENDIF
3125             IF ( .NOT. root_area_density_lsm_f%from_file )  THEN
3126                message_string = 'If vegetation_type = 0 at any location, ' // &
3127                                 'root_area_dens_s is required'
3128                CALL message( 'netcdf_data_input_mod', 'PA0556', 2, 2, myid, 6, 0 )
3129             ENDIF
3130          ENDIF
3131       ENDIF
3132!
3133!--    If soil_type is zero at any location, soil_pars is required.
3134       IF ( soil_type_f%from_file )  THEN
3135          check_passed = .TRUE.
3136          IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
3137             IF ( ANY( soil_type_f%var_2d == 0 ) )  THEN
3138                IF ( .NOT. soil_pars_f%from_file )  check_passed = .FALSE.
3139             ENDIF
3140          ELSE
3141             IF ( ANY( soil_type_f%var_3d == 0 ) )  THEN
3142                IF ( .NOT. soil_pars_f%from_file )  check_passed = .FALSE.
3143             ENDIF
3144          ENDIF
3145          IF ( .NOT. check_passed )  THEN
3146             message_string = 'If soil_type = 0 at any location, ' //          &
3147                              'soil_pars is required'
3148             CALL message( 'netcdf_data_input_mod', 'PA0557', 2, 2, myid, 6, 0 )
3149          ENDIF
3150       ENDIF
3151!
3152!--    If building_type is zero at any location, building_pars is required.
3153       IF ( building_type_f%from_file )  THEN
3154          IF ( ANY( building_type_f%var == 0 ) )  THEN
3155             IF ( .NOT. building_pars_f%from_file )  THEN
3156                message_string = 'If building_type = 0 at any location, ' //   &
3157                                 'building_pars is required'
3158                CALL message( 'netcdf_data_input_mod', 'PA0558', 2, 2, myid, 6, 0 )
3159             ENDIF
3160          ENDIF
3161       ENDIF
3162!
3163!--    If albedo_type is zero at any location, albedo_pars is required.
3164       IF ( albedo_type_f%from_file )  THEN
3165          IF ( ANY( albedo_type_f%var == 0 ) )  THEN
3166             IF ( .NOT. albedo_pars_f%from_file )  THEN
3167                message_string = 'If albedo_type = 0 at any location, ' //     &
3168                                 'albedo_pars is required'
3169                CALL message( 'netcdf_data_input_mod', 'PA0559', 2, 2, myid, 6, 0 )
3170             ENDIF
3171          ENDIF
3172       ENDIF
3173!
3174!--    If pavement_type is zero at any location, pavement_pars is required.
3175       IF ( pavement_type_f%from_file )  THEN
3176          IF ( ANY( pavement_type_f%var == 0 ) )  THEN
3177             IF ( .NOT. pavement_pars_f%from_file )  THEN
3178                message_string = 'If pavement_type = 0 at any location, ' //   &
3179                                 'pavement_pars is required'
3180                CALL message( 'netcdf_data_input_mod', 'PA0560', 2, 2, myid, 6, 0 )
3181             ENDIF
3182          ENDIF
3183       ENDIF
3184!
3185!--    If pavement_type is zero at any location, also pavement_subsurface_pars
3186!--    is required.
3187       IF ( pavement_type_f%from_file )  THEN
3188          IF ( ANY( pavement_type_f%var == 0 ) )  THEN
3189             IF ( .NOT. pavement_subsurface_pars_f%from_file )  THEN
3190                message_string = 'If pavement_type = 0 at any location, ' //   &
3191                                 'pavement_subsurface_pars is required'
3192                CALL message( 'netcdf_data_input_mod', 'PA0561', 2, 2, myid, 6, 0 )
3193             ENDIF
3194          ENDIF
3195       ENDIF
3196!
3197!--    If water_type is zero at any location, water_pars is required.
3198       IF ( water_type_f%from_file )  THEN
3199          IF ( ANY( water_type_f%var == 0 ) )  THEN
3200             IF ( .NOT. water_pars_f%from_file )  THEN
3201                message_string = 'If water_type = 0 at any location, ' //      &
3202                                 'water_pars is required'
3203                CALL message( 'netcdf_data_input_mod', 'PA0562', 2, 2,myid, 6, 0 )
3204             ENDIF
3205          ENDIF
3206       ENDIF
3207!
3208!--    Check for local consistency of the input data.
3209       DO  i = nxl, nxr
3210          DO  j = nys, nyn
3211!
3212!--          For each (y,x)-location at least one of the parameters
3213!--          vegetation_type, pavement_type, building_type, or water_type
3214!--          must be set to a non­missing value.
3215             IF ( vegetation_type_f%var(j,i) == vegetation_type_f%fill  .AND.  &
3216                  pavement_type_f%var(j,i)   == pavement_type_f%fill    .AND.  &
3217                  building_type_f%var(j,i)   == building_type_f%fill    .AND.  &
3218                  water_type_f%var(j,i)      == water_type_f%fill )  THEN
3219                WRITE( message_string, * ) 'At least one of the parameters '// &
3220                                 'vegetation_type, pavement_type, '     //     &
3221                                 'building_type, or water_type must be set '// &
3222                                 'to a non-missing value. Grid point: ', j, i
3223                CALL message( 'netcdf_data_input_mod', 'PA0563', 2, 2, myid, 6, 0 )
3224             ENDIF
3225!
3226!--          Note that a soil_type is required for each location (y,x) where
3227!--          either vegetation_type or pavement_type is a non­missing value.
3228             IF ( ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill  .OR. &
3229                    pavement_type_f%var(j,i)   /= pavement_type_f%fill ) )  THEN
3230                check_passed = .TRUE.
3231                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
3232                   IF ( soil_type_f%var_2d(j,i) == soil_type_f%fill )          &
3233                      check_passed = .FALSE.
3234                ELSE
3235                   IF ( ANY( soil_type_f%var_3d(:,j,i) == soil_type_f%fill) )  &
3236                      check_passed = .FALSE.
3237                ENDIF
3238
3239                IF ( .NOT. check_passed )  THEN
3240                   message_string = 'soil_type is required for each '//        &
3241                                 'location (y,x) where vegetation_type or ' // &
3242                                 'pavement_type is a non-missing value.'
3243                   CALL message( 'netcdf_data_input_mod', 'PA0564',            &
3244                                  2, 2, myid, 6, 0 )
3245                ENDIF
3246             ENDIF
3247!
3248!--          Check for consistency of surface fraction. If more than one type
3249!--          is set, surface fraction need to be given and the sum must not
3250!--          be larger than 1.
3251             n_surf = 0
3252             IF ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill )       &
3253                n_surf = n_surf + 1
3254             IF ( water_type_f%var(j,i)      /= water_type_f%fill )            &
3255                n_surf = n_surf + 1
3256             IF ( pavement_type_f%var(j,i)   /= pavement_type_f%fill )         &
3257                n_surf = n_surf + 1
3258
3259             IF ( n_surf > 1 )  THEN
3260                IF ( .NOT. surface_fraction_f%from_file )  THEN
3261                   message_string = 'If more than one surface type is ' //     &
3262                                 'given at a location, surface_fraction ' //   &
3263                                 'must be provided.'
3264                   CALL message( 'netcdf_data_input_mod', 'PA0565',            &
3265                                  2, 2, myid, 6, 0 )
3266                ELSEIF ( ANY ( surface_fraction_f%frac(:,j,i) ==               &
3267                               surface_fraction_f%fill ) )  THEN
3268                   message_string = 'If more than one surface type is ' //     &
3269                                 'given at a location, surface_fraction ' //   &
3270                                 'must be provided.'
3271                   CALL message( 'netcdf_data_input_mod', 'PA0565',            &
3272                                  2, 2, myid, 6, 0 )
3273                ENDIF
3274             ENDIF
3275!
3276!--          Check for further mismatches. e.g. relative fractions exceed 1 or
3277!--          vegetation_type is set but surface vegetation fraction is zero,
3278!--          etc..
3279             IF ( surface_fraction_f%from_file )  THEN
3280!
3281!--             Sum of relative fractions must not exceed 1.
3282                IF ( SUM ( surface_fraction_f%frac(0:2,j,i) ) > 1.0_wp )  THEN
3283                   message_string = 'surface_fraction must not exceed 1'
3284                   CALL message( 'netcdf_data_input_mod', 'PA0566',            &
3285                                  2, 2, myid, 6, 0 )
3286                ENDIF
3287!
3288!--             Relative fraction for a type must not be zero at locations where
3289!--             this type is set.
3290                IF (                                                           &
3291                  ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill  .AND.&
3292                 ( surface_fraction_f%frac(ind_veg_wall,j,i) == 0.0_wp .OR.    &
3293                   surface_fraction_f%frac(ind_veg_wall,j,i) ==                &
3294                                                     surface_fraction_f%fill ) &
3295                  )  .OR.                                                      &
3296                  ( pavement_type_f%var(j,i) /= pavement_type_f%fill     .AND. &
3297                 ( surface_fraction_f%frac(ind_pav_green,j,i) == 0.0_wp .OR.   &
3298                   surface_fraction_f%frac(ind_pav_green,j,i) ==               &
3299                                                     surface_fraction_f%fill ) &
3300                  )  .OR.                                                      &
3301                  ( water_type_f%var(j,i) /= water_type_f%fill           .AND. &
3302                 ( surface_fraction_f%frac(ind_wat_win,j,i) == 0.0_wp .OR.     &
3303                   surface_fraction_f%frac(ind_wat_win,j,i) ==                 &
3304                                                     surface_fraction_f%fill ) &
3305                  ) )  THEN
3306                   WRITE( message_string, * ) 'Mismatch in setting of '     // &
3307                             'surface_fraction. Vegetation-, pavement-, or '// &
3308                             'water surface is given at (i,j) = ( ', i, j,     &
3309                             ' ), but surface fraction is 0 for the given type.'
3310                   CALL message( 'netcdf_data_input_mod', 'PA0567',            &
3311                                  2, 2, myid, 6, 0 )
3312                ENDIF
3313!
3314!--             Relative fraction for a type must not contain non-zero values
3315!--             if this type is not set.
3316                IF (                                                           &
3317                  ( vegetation_type_f%var(j,i) == vegetation_type_f%fill  .AND.&
3318                 ( surface_fraction_f%frac(ind_veg_wall,j,i) /= 0.0_wp .AND.   &
3319                   surface_fraction_f%frac(ind_veg_wall,j,i) /=                &
3320                                                     surface_fraction_f%fill ) &
3321                  )  .OR.                                                      &
3322                  ( pavement_type_f%var(j,i) == pavement_type_f%fill     .AND. &
3323                 ( surface_fraction_f%frac(ind_pav_green,j,i) /= 0.0_wp .AND.  &
3324                   surface_fraction_f%frac(ind_pav_green,j,i) /=               &
3325                                                     surface_fraction_f%fill ) &
3326                  )  .OR.                                                      &
3327                  ( water_type_f%var(j,i) == water_type_f%fill           .AND. &
3328                 ( surface_fraction_f%frac(ind_wat_win,j,i) /= 0.0_wp .AND.    &
3329                   surface_fraction_f%frac(ind_wat_win,j,i) /=                 &
3330                                                     surface_fraction_f%fill ) &
3331                  ) )  THEN
3332                   WRITE( message_string, * ) 'Mismatch in setting of '     // &
3333                             'surface_fraction. Vegetation-, pavement-, or '// &
3334                             'water surface is not given at (i,j) = ( ', i, j, &
3335                             ' ), but surface fraction is not 0 for the ' //   &
3336                             'given type.'
3337                   CALL message( 'netcdf_data_input_mod', 'PA0568',            &
3338                                  2, 2, myid, 6, 0 )
3339                ENDIF
3340             ENDIF
3341!
3342!--          Check vegetation_pars. If vegetation_type is 0, all parameters
3343!--          need to be set, otherwise, single parameters set by
3344!--          vegetation_type can be overwritten.
3345             IF ( vegetation_type_f%from_file )  THEN
3346                IF ( vegetation_type_f%var(j,i) == 0 )  THEN
3347                   IF ( ANY( vegetation_pars_f%pars_xy(:,j,i) ==               &
3348                             vegetation_pars_f%fill ) )  THEN
3349                      message_string = 'If vegetation_type(y,x) = 0, all '  // &
3350                                       'parameters of vegetation_pars at '//   &
3351                                       'this location must be set.'
3352                      CALL message( 'netcdf_data_input_mod', 'PA0569',         &
3353                                     2, 2, myid, 6, 0 )
3354                   ENDIF
3355                ENDIF
3356             ENDIF
3357!
3358!--          Check root distribution. If vegetation_type is 0, all levels must
3359!--          be set.
3360             IF ( vegetation_type_f%from_file )  THEN
3361                IF ( vegetation_type_f%var(j,i) == 0 )  THEN
3362                   IF ( ANY( root_area_density_lsm_f%var(:,j,i) ==             &
3363                             root_area_density_lsm_f%fill ) )  THEN
3364                      message_string = 'If vegetation_type(y,x) = 0, all ' //  &
3365                                       'levels of root_area_dens_s ' //        &
3366                                       'must be set at this location.'
3367                      CALL message( 'netcdf_data_input_mod', 'PA0570',         &
3368                                     2, 2, myid, 6, 0 )
3369                   ENDIF
3370                ENDIF
3371             ENDIF
3372!
3373!--          Check soil parameters. If soil_type is 0, all parameters
3374!--          must be set.
3375             IF ( soil_type_f%from_file )  THEN
3376                check_passed = .TRUE.
3377                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
3378                   IF ( soil_type_f%var_2d(j,i) == 0 )  THEN
3379                      IF ( ANY( soil_pars_f%pars_xy(:,j,i) ==                  &
3380                                soil_pars_f%fill ) )  check_passed = .FALSE.
3381                   ENDIF
3382                ELSE
3383                   IF ( ANY( soil_type_f%var_3d(:,j,i) == 0 ) )  THEN
3384                      IF ( ANY( soil_pars_f%pars_xy(:,j,i) ==                  &
3385                                soil_pars_f%fill ) )  check_passed = .FALSE.
3386                   ENDIF
3387                ENDIF
3388                IF ( .NOT. check_passed )  THEN
3389                   message_string = 'If soil_type(y,x) = 0, all levels of '  //&
3390                                    'soil_pars at this location must be set.'
3391                   CALL message( 'netcdf_data_input_mod', 'PA0571',            &
3392                                  2, 2, myid, 6, 0 )
3393                ENDIF
3394             ENDIF
3395
3396!
3397!--          Check building parameters. If building_type is 0, all parameters
3398!--          must be set.
3399             IF ( building_type_f%from_file )  THEN
3400                IF ( building_type_f%var(j,i) == 0 )  THEN
3401                   IF ( ANY( building_pars_f%pars_xy(:,j,i) ==                 &
3402                             building_pars_f%fill ) )  THEN
3403                      message_string = 'If building_type(y,x) = 0, all ' //    &
3404                                       'parameters of building_pars at this '//&
3405                                       'location must be set.'
3406                      CALL message( 'netcdf_data_input_mod', 'PA0572',         &
3407                                     2, 2, myid, 6, 0 )
3408                   ENDIF
3409                ENDIF
3410             ENDIF
3411!
3412!--          Check if building_type is set at each building and vice versa.
3413             IF ( building_type_f%from_file  .AND.  buildings_f%from_file )  THEN
3414                IF ( buildings_f%lod == 1 )  THEN
3415                   IF ( buildings_f%var_2d(j,i)  /= buildings_f%fill1  .AND.   &
3416                        building_type_f%var(j,i) == building_type_f%fill )  THEN
3417                      WRITE( message_string, * ) 'Each location where a ' //   &
3418                                         'building is set requires a type ' // &
3419                                         '( and vice versa ) in case the ' //  &
3420                                         'urban-surface model is applied. ' // &
3421                                         'i, j = ', i, j
3422                      CALL message( 'netcdf_data_input_mod', 'PA0573',         &
3423                                     2, 2, myid, 6, 0 )
3424                   ENDIF
3425                ENDIF
3426                IF ( buildings_f%lod == 2 )  THEN
3427                   IF ( ANY( buildings_f%var_3d(:,j,i) == 1 )  .AND.           &
3428                        building_type_f%var(j,i) == building_type_f%fill )  THEN
3429                      WRITE( message_string, * ) 'Each location where a ' //   &
3430                                         'building is set requires a type ' // &
3431                                         '( and vice versa ) in case the ' //  &
3432                                         'urban-surface model is applied. ' // &
3433                                         'i, j = ', i, j
3434                      CALL message( 'netcdf_data_input_mod', 'PA0573',         &
3435                                     2, 2, myid, 6, 0 )
3436                   ENDIF
3437                ENDIF
3438             ENDIF
3439!
3440!--          Check if at each location where a building is present also an ID
3441!--          is set and vice versa.
3442             IF ( buildings_f%from_file )  THEN
3443                IF ( buildings_f%lod == 1 )  THEN
3444                   IF ( buildings_f%var_2d(j,i) /= buildings_f%fill1  .AND.    &
3445                        building_id_f%var(j,i)  == building_id_f%fill )  THEN
3446                      WRITE( message_string, * ) 'Each location where a ' //   &
3447                                         'building is set requires an ID ' //  &
3448                                         '( and vice versa ). i, j = ', i, j
3449                      CALL message( 'netcdf_data_input_mod', 'PA0574',         &
3450                                     2, 2, myid, 6, 0 )
3451                   ENDIF
3452                ELSEIF ( buildings_f%lod == 2 )  THEN
3453                   IF ( ANY( buildings_f%var_3d(:,j,i) == 1 )  .AND.           &
3454                        building_id_f%var(j,i) == building_id_f%fill )  THEN
3455                      WRITE( message_string, * ) 'Each location where a ' //   &
3456                                         'building is set requires an ID ' //  &
3457                                         '( and vice versa ). i, j = ', i, j
3458                      CALL message( 'netcdf_data_input_mod', 'PA0574',         &
3459                                     2, 2, myid, 6, 0 )
3460                   ENDIF
3461                ENDIF
3462             ENDIF
3463!
3464!--          Check if building ID is set where a bulding is defined.
3465             IF ( buildings_f%from_file )  THEN
3466                IF ( buildings_f%lod == 1 )  THEN
3467                   IF ( buildings_f%var_2d(j,i) /= buildings_f%fill1  .AND.   &
3468                        building_id_f%var(j,i)  == building_id_f%fill )  THEN
3469                      WRITE( message_string, * ) 'Each building grid point '// &
3470                                                 'requires an ID.', i, j
3471                      CALL message( 'netcdf_data_input_mod', 'PA0575',         &
3472                                     2, 2, myid, 6, 0 )
3473                   ENDIF
3474                ELSEIF ( buildings_f%lod == 2 )  THEN
3475                   IF ( ANY( buildings_f%var_3d(:,j,i) == 1 )  .AND.           &
3476                        building_id_f%var(j,i) == building_id_f%fill )  THEN
3477                      WRITE( message_string, * ) 'Each building grid point '// &
3478                                                 'requires an ID.', i, j
3479                      CALL message( 'netcdf_data_input_mod', 'PA0575',         &
3480                                     2, 2, myid, 6, 0 )
3481                   ENDIF
3482                ENDIF
3483             ENDIF
3484!
3485!--          Check albedo parameters. If albedo_type is 0, all parameters
3486!--          must be set.
3487             IF ( albedo_type_f%from_file )  THEN
3488                IF ( albedo_type_f%var(j,i) == 0 )  THEN
3489                   IF ( ANY( albedo_pars_f%pars_xy(:,j,i) ==                   &
3490                             albedo_pars_f%fill ) )  THEN
3491                      message_string = 'If albedo_type(y,x) = 0, all ' //      &
3492                                       'parameters of albedo_pars at this ' // &
3493                                       'location must be set.'
3494                      CALL message( 'netcdf_data_input_mod', 'PA0576',         &
3495                                     2, 2, myid, 6, 0 )
3496                   ENDIF
3497                ENDIF
3498             ENDIF
3499
3500!
3501!--          Check pavement parameters. If pavement_type is 0, all parameters
3502!--          of pavement_pars must be set at this location.
3503             IF ( pavement_type_f%from_file )  THEN
3504                IF ( pavement_type_f%var(j,i) == 0 )  THEN
3505                   IF ( ANY( pavement_pars_f%pars_xy(:,j,i) ==                 &
3506                             pavement_pars_f%fill ) )  THEN
3507                      message_string = 'If pavement_type(y,x) = 0, all ' //    &
3508                                       'parameters of pavement_pars at this '//&
3509                                       'location must be set.'
3510                      CALL message( 'netcdf_data_input_mod', 'PA0577',         &
3511                                     2, 2, myid, 6, 0 )
3512                   ENDIF
3513                ENDIF
3514             ENDIF
3515!
3516!--          Check pavement-subsurface parameters. If pavement_type is 0,
3517!--          all parameters of pavement_subsurface_pars must be set  at this
3518!--          location.
3519             IF ( pavement_type_f%from_file )  THEN
3520                IF ( pavement_type_f%var(j,i) == 0 )  THEN
3521                   IF ( ANY( pavement_subsurface_pars_f%pars_xyz(:,:,j,i) ==   &
3522                             pavement_subsurface_pars_f%fill ) )  THEN
3523                      message_string = 'If pavement_type(y,x) = 0, all ' //    &
3524                                       'parameters of '                  //    &
3525                                       'pavement_subsurface_pars at this '//   &
3526                                       'location must be set.'
3527                      CALL message( 'netcdf_data_input_mod', 'PA0578',         &
3528                                     2, 2, myid, 6, 0 )
3529                   ENDIF
3530                ENDIF
3531             ENDIF
3532
3533!
3534!--          Check water parameters. If water_type is 0, all parameters
3535!--          must be set  at this location.
3536             IF ( water_type_f%from_file )  THEN
3537                IF ( water_type_f%var(j,i) == 0 )  THEN
3538                   IF ( ANY( water_pars_f%pars_xy(:,j,i) ==                    &
3539                             water_pars_f%fill ) )  THEN
3540                      message_string = 'If water_type(y,x) = 0, all ' //       &
3541                                       'parameters of water_pars at this ' //  &
3542                                       'location must be set.'
3543                      CALL message( 'netcdf_data_input_mod', 'PA0579',         &
3544                                     2, 2, myid, 6, 0 )
3545                   ENDIF
3546                ENDIF
3547             ENDIF
3548
3549          ENDDO
3550       ENDDO
3551
3552    END SUBROUTINE netcdf_data_input_check_static
3553
3554!------------------------------------------------------------------------------!
3555! Description:
3556! ------------
3557!> Vertical interpolation and extrapolation of 1D variables.
3558!------------------------------------------------------------------------------!
3559    SUBROUTINE netcdf_data_input_interpolate_1d( var, z_grid, z_file)
3560
3561       IMPLICIT NONE
3562
3563       INTEGER(iwp) ::  k       !< running index z-direction file
3564       INTEGER(iwp) ::  kk      !< running index z-direction stretched model grid
3565       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
3566       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
3567
3568       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
3569       REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid
3570       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var      !< treated variable
3571       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var_tmp  !< temporary variable
3572
3573
3574       kl = LBOUND(var,1)
3575       ku = UBOUND(var,1)
3576       ALLOCATE( var_tmp(kl:ku) )
3577
3578       DO  k = kl, ku
3579
3580          kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
3581
3582          IF ( kk < ku )  THEN
3583             IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
3584                var_tmp(k) = var(kk) +                                         &
3585                                       ( var(kk+1)        - var(kk)    ) /     &
3586                                       ( z_file(kk+1)     - z_file(kk) ) *     &
3587                                       ( z_grid(k)        - z_file(kk) )
3588
3589             ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
3590                var_tmp(k) = var(kk-1) +                                       &
3591                                         ( var(kk)     - var(kk-1)    ) /      &
3592                                         ( z_file(kk)  - z_file(kk-1) ) *      &
3593                                         ( z_grid(k)   - z_file(kk-1) )
3594             ENDIF
3595!
3596!--       Extrapolate
3597          ELSE
3598
3599             var_tmp(k) = var(ku) +   ( var(ku)    - var(ku-1)      ) /        &
3600                                      ( z_file(ku) - z_file(ku-1)   ) *        &
3601                                      ( z_grid(k)  - z_file(ku)     )
3602
3603          ENDIF
3604
3605       ENDDO
3606       var(:) = var_tmp(:)
3607
3608       DEALLOCATE( var_tmp )
3609
3610
3611    END SUBROUTINE netcdf_data_input_interpolate_1d
3612
3613
3614!------------------------------------------------------------------------------!
3615! Description:
3616! ------------
3617!> Vertical interpolation and extrapolation of 1D variables from Inifor grid
3618!> onto Palm grid, where both have same dimension. Please note, the passed
3619!> paramter list in 1D version is different compared to 2D version.
3620!------------------------------------------------------------------------------!
3621    SUBROUTINE netcdf_data_input_interpolate_1d_soil( var, var_file,           &
3622                                                      z_grid, z_file,          &
3623                                                      nzb_var, nzt_var,        &
3624                                                      nzb_file, nzt_file )
3625
3626       IMPLICIT NONE
3627
3628       INTEGER(iwp) ::  k        !< running index z-direction file
3629       INTEGER(iwp) ::  kk       !< running index z-direction stretched model grid
3630       INTEGER(iwp) ::  ku       !< upper index bound along z-direction for varialbe from file
3631       INTEGER(iwp) ::  nzb_var  !< lower bound of final array
3632       INTEGER(iwp) ::  nzt_var  !< upper bound of final array
3633       INTEGER(iwp) ::  nzb_file !< lower bound of file array
3634       INTEGER(iwp) ::  nzt_file !< upper bound of file array
3635
3636!        LOGICAL, OPTIONAL ::  zsoil !< flag indicating reverse z-axis, i.e. zsoil instead of height, e.g. in case of ocean or soil
3637
3638       REAL(wp), DIMENSION(nzb_var:nzt_var)   ::  z_grid   !< grid levels on numeric grid
3639       REAL(wp), DIMENSION(nzb_file:nzt_file) ::  z_file   !< grid levels on file grid
3640       REAL(wp), DIMENSION(nzb_var:nzt_var)   ::  var      !< treated variable
3641       REAL(wp), DIMENSION(nzb_file:nzt_file) ::  var_file !< temporary variable
3642
3643       ku = nzt_file
3644
3645       DO  k = nzb_var, nzt_var
3646!
3647!--       Determine index on Inifor grid which is closest to the actual height
3648          kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
3649!
3650!--       If closest index on Inifor grid is smaller than top index,
3651!--       interpolate the data
3652          IF ( kk < nzt_file )  THEN
3653             IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
3654                var(k) = var_file(kk) + ( var_file(kk+1) - var_file(kk) ) /    &
3655                                        ( z_file(kk+1)   - z_file(kk)   ) *    &
3656                                        ( z_grid(k)      - z_file(kk)   )
3657
3658             ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
3659                var(k) = var_file(kk-1) + ( var_file(kk) - var_file(kk-1) ) /  &
3660                                          ( z_file(kk)   - z_file(kk-1)   ) *  &
3661                                          ( z_grid(k)    - z_file(kk-1)   )
3662             ENDIF
3663!
3664!--       Extrapolate if actual height is above the highest Inifor level
3665          ELSE
3666             var(k) = var_file(ku) + ( var_file(ku) - var_file(ku-1) ) /       &
3667                                     ( z_file(ku)   - z_file(ku-1)   ) *       &
3668                                     ( z_grid(k)    - z_file(ku)     )
3669
3670          ENDIF
3671
3672       ENDDO
3673
3674    END SUBROUTINE netcdf_data_input_interpolate_1d_soil
3675
3676!------------------------------------------------------------------------------!
3677! Description:
3678! ------------
3679!> Vertical interpolation and extrapolation of 2D variables at lateral boundaries.
3680!------------------------------------------------------------------------------!
3681    SUBROUTINE netcdf_data_input_interpolate_2d( var, z_grid, z_file)
3682
3683       IMPLICIT NONE
3684
3685       INTEGER(iwp) ::  i       !< running index x- or y -direction
3686       INTEGER(iwp) ::  il      !< lower index bound along x- or y-direction
3687       INTEGER(iwp) ::  iu      !< upper index bound along x- or y-direction
3688       INTEGER(iwp) ::  k       !< running index z-direction file
3689       INTEGER(iwp) ::  kk      !< running index z-direction stretched model grid
3690       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
3691       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
3692
3693       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
3694       REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid
3695       REAL(wp), DIMENSION(:,:), INTENT(INOUT) ::  var    !< treated variable
3696       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var_tmp  !< temporary variable
3697
3698
3699       il = LBOUND(var,2)
3700       iu = UBOUND(var,2)
3701       kl = LBOUND(var,1)
3702       ku = UBOUND(var,1)
3703       ALLOCATE( var_tmp(kl:ku) )
3704
3705       DO  i = il, iu
3706          DO  k = kl, ku
3707
3708             kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
3709
3710             IF ( kk < ku )  THEN
3711                IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
3712                   var_tmp(k) = var(kk,i) +                                    &
3713                                          ( var(kk+1,i)      - var(kk,i)  ) /  &
3714                                          ( z_file(kk+1)     - z_file(kk) ) *  &
3715                                          ( z_grid(k)        - z_file(kk) )
3716
3717                ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
3718                   var_tmp(k) = var(kk-1,i) +                                  &
3719                                            ( var(kk,i)   - var(kk-1,i)  ) /   &
3720                                            ( z_file(kk)  - z_file(kk-1) ) *   &
3721                                            ( z_grid(k)   - z_file(kk-1) )
3722                ENDIF
3723!
3724!--          Extrapolate
3725             ELSE
3726
3727                var_tmp(k) = var(ku,i) + ( var(ku,i)  - var(ku-1,i)    ) /     &
3728                                         ( z_file(ku) - z_file(ku-1)   ) *     &
3729                                         ( z_grid(k)  - z_file(ku)     )
3730
3731             ENDIF
3732
3733          ENDDO
3734          var(:,i) = var_tmp(:)
3735
3736       ENDDO
3737
3738       DEALLOCATE( var_tmp )
3739
3740
3741    END SUBROUTINE netcdf_data_input_interpolate_2d
3742
3743!------------------------------------------------------------------------------!
3744! Description:
3745! ------------
3746!> Vertical interpolation and extrapolation of 3D variables.
3747!------------------------------------------------------------------------------!
3748    SUBROUTINE netcdf_data_input_interpolate_3d( var, z_grid, z_file )
3749
3750       IMPLICIT NONE
3751
3752       INTEGER(iwp) ::  i       !< running index x-direction
3753       INTEGER(iwp) ::  il      !< lower index bound along x-direction
3754       INTEGER(iwp) ::  iu      !< upper index bound along x-direction
3755       INTEGER(iwp) ::  j       !< running index y-direction
3756       INTEGER(iwp) ::  jl      !< lower index bound along x-direction
3757       INTEGER(iwp) ::  ju      !< upper index bound along x-direction
3758       INTEGER(iwp) ::  k       !< running index z-direction file
3759       INTEGER(iwp) ::  kk      !< running index z-direction stretched model grid
3760       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
3761       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
3762
3763       REAL(wp), DIMENSION(:) ::  z_grid                      !< grid levels on numeric grid
3764       REAL(wp), DIMENSION(:) ::  z_file                      !< grid levels on file grid
3765       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var      !< treated variable
3766       REAL(wp), DIMENSION(:), ALLOCATABLE       ::  var_tmp  !< temporary variable
3767
3768       il = LBOUND(var,3)
3769       iu = UBOUND(var,3)
3770       jl = LBOUND(var,2)
3771       ju = UBOUND(var,2)
3772       kl = LBOUND(var,1)
3773       ku = UBOUND(var,1)
3774
3775       ALLOCATE( var_tmp(kl:ku) )
3776
3777       DO  i = il, iu
3778          DO  j = jl, ju
3779             DO  k = kl, ku
3780
3781                kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
3782
3783                IF ( kk < ku )  THEN
3784                   IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
3785                      var_tmp(k) = var(kk,j,i) +                               &
3786                                             ( var(kk+1,j,i) - var(kk,j,i) ) / &
3787                                             ( z_file(kk+1)  - z_file(kk)  ) * &
3788                                             ( z_grid(k)     - z_file(kk)  )
3789
3790                   ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
3791                      var_tmp(k) = var(kk-1,j,i) +                             &
3792                                             ( var(kk,j,i) - var(kk-1,j,i) ) / &
3793                                             ( z_file(kk)  - z_file(kk-1)  ) * &
3794                                             ( z_grid(k)   - z_file(kk-1)  )
3795                   ENDIF
3796!
3797!--             Extrapolate
3798                ELSE
3799                   var_tmp(k) = var(ku,j,i) +                                  &
3800                                       ( var(ku,j,i)  - var(ku-1,j,i)   ) /    &
3801                                       ( z_file(ku)   - z_file(ku-1)    ) *    &
3802                                       ( z_grid(k)    - z_file(ku)      )
3803
3804                ENDIF
3805             ENDDO
3806             var(:,j,i) = var_tmp(:)
3807          ENDDO
3808       ENDDO
3809
3810       DEALLOCATE( var_tmp )
3811
3812
3813    END SUBROUTINE netcdf_data_input_interpolate_3d
3814
3815!------------------------------------------------------------------------------!
3816! Description:
3817! ------------
3818!> Checks if a given variables is on file
3819!------------------------------------------------------------------------------!
3820    FUNCTION check_existence( vars_in_file, var_name )
3821
3822       IMPLICIT NONE
3823
3824       CHARACTER(LEN=*) ::  var_name                   !< variable to be checked
3825       CHARACTER(LEN=*), DIMENSION(:) ::  vars_in_file !< list of variables in file
3826
3827       INTEGER(iwp) ::  i                              !< loop variable
3828
3829       LOGICAL ::  check_existence                     !< flag indicating whether a variable exist or not - actual return value
3830
3831       i = 1
3832       check_existence = .FALSE.
3833       DO  WHILE ( i <= SIZE( vars_in_file ) )
3834          check_existence = TRIM( vars_in_file(i) ) == TRIM( var_name )  .OR.  &
3835                            check_existence
3836          i = i + 1
3837       ENDDO
3838
3839       RETURN
3840
3841    END FUNCTION check_existence
3842
3843
3844!------------------------------------------------------------------------------!
3845! Description:
3846! ------------
3847!> Closes an existing netCDF file.
3848!------------------------------------------------------------------------------!
3849    SUBROUTINE close_input_file( id )
3850#if defined( __netcdf )
3851
3852       USE pegrid
3853
3854       IMPLICIT NONE
3855
3856       INTEGER(iwp), INTENT(INOUT)        ::  id        !< file id
3857
3858       nc_stat = NF90_CLOSE( id )
3859       CALL handle_error( 'close', 540 )
3860#endif
3861    END SUBROUTINE close_input_file
3862
3863!------------------------------------------------------------------------------!
3864! Description:
3865! ------------
3866!> Opens an existing netCDF file for reading only and returns its id.
3867!------------------------------------------------------------------------------!
3868    SUBROUTINE open_read_file( filename, id )
3869#if defined( __netcdf )
3870
3871       USE pegrid
3872
3873       IMPLICIT NONE
3874
3875       CHARACTER (LEN=*), INTENT(IN) ::  filename  !< filename
3876       INTEGER(iwp), INTENT(INOUT)   ::  id        !< file id
3877
3878#if defined( __netcdf4_parallel )
3879!      if __netcdf4_parallel is defined, parrallel NetCDF will be used unconditionally
3880       nc_stat = NF90_OPEN( filename, IOR( NF90_WRITE, NF90_MPIIO ), id,  &
3881                            COMM = comm2d, INFO = MPI_INFO_NULL )
3882       IF(nc_stat /= NF90_NOERR )  THEN                                       !possible NetCDF 3 file
3883           nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
3884           collective_read = .FALSE.
3885       ELSE
3886           collective_read = .TRUE.
3887       END IF
3888#else
3889!      All MPI processes open und read
3890       nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
3891#endif
3892
3893       CALL handle_error( 'open_read_file', 539 )
3894
3895#endif
3896    END SUBROUTINE open_read_file
3897
3898!------------------------------------------------------------------------------!
3899! Description:
3900! ------------
3901!> Reads global or variable-related attributes of type INTEGER (32-bit)
3902!------------------------------------------------------------------------------!
3903     SUBROUTINE get_attribute_int32( id, attribute_name, value, global,        &
3904                                     variable_name )
3905
3906       USE pegrid
3907
3908       IMPLICIT NONE
3909
3910       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
3911       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
3912
3913       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
3914       INTEGER(iwp)                ::  id_var           !< variable id
3915       INTEGER(iwp), INTENT(INOUT) ::  value            !< read value
3916
3917       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
3918#if defined( __netcdf )
3919
3920!
3921!--    Read global attribute
3922       IF ( global )  THEN
3923          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
3924          CALL handle_error( 'get_attribute_int32 global', 522, attribute_name )
3925!
3926!--    Read attributes referring to a single variable. Therefore, first inquire
3927!--    variable id
3928       ELSE
3929          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
3930          CALL handle_error( 'get_attribute_int32', 522, attribute_name )
3931          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
3932          CALL handle_error( 'get_attribute_int32', 522, attribute_name )
3933       ENDIF
3934#endif
3935    END SUBROUTINE get_attribute_int32
3936
3937!------------------------------------------------------------------------------!
3938! Description:
3939! ------------
3940!> Reads global or variable-related attributes of type INTEGER (8-bit)
3941!------------------------------------------------------------------------------!
3942     SUBROUTINE get_attribute_int8( id, attribute_name, value, global,         &
3943                                    variable_name )
3944
3945       USE pegrid
3946
3947       IMPLICIT NONE
3948
3949       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
3950       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
3951
3952       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
3953       INTEGER(iwp)                ::  id_var           !< variable id
3954       INTEGER(KIND=1), INTENT(INOUT) ::  value         !< read value
3955
3956       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
3957#if defined( __netcdf )
3958
3959!
3960!--    Read global attribute
3961       IF ( global )  THEN
3962          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
3963          CALL handle_error( 'get_attribute_int8 global', 523, attribute_name )
3964!
3965!--    Read attributes referring to a single variable. Therefore, first inquire
3966!--    variable id
3967       ELSE
3968          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
3969          CALL handle_error( 'get_attribute_int8', 523, attribute_name )
3970          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
3971          CALL handle_error( 'get_attribute_int8', 523, attribute_name )
3972       ENDIF
3973#endif
3974    END SUBROUTINE get_attribute_int8
3975
3976!------------------------------------------------------------------------------!
3977! Description:
3978! ------------
3979!> Reads global or variable-related attributes of type REAL
3980!------------------------------------------------------------------------------!
3981     SUBROUTINE get_attribute_real( id, attribute_name, value, global,         &
3982                                    variable_name )
3983
3984       USE pegrid
3985
3986       IMPLICIT NONE
3987
3988       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
3989       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
3990
3991       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
3992       INTEGER(iwp)                ::  id_var           !< variable id
3993
3994       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
3995
3996       REAL(wp), INTENT(INOUT)     ::  value            !< read value
3997#if defined( __netcdf )
3998
3999
4000!
4001!-- Read global attribute
4002       IF ( global )  THEN
4003          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
4004          CALL handle_error( 'get_attribute_real global', 524, attribute_name )
4005!
4006!-- Read attributes referring to a single variable. Therefore, first inquire
4007!-- variable id
4008       ELSE
4009          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4010          CALL handle_error( 'get_attribute_real', 524, attribute_name )
4011          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
4012          CALL handle_error( 'get_attribute_real', 524, attribute_name )
4013       ENDIF
4014#endif
4015    END SUBROUTINE get_attribute_real
4016
4017!------------------------------------------------------------------------------!
4018! Description:
4019! ------------
4020!> Reads global or variable-related attributes of type CHARACTER
4021!> Remark: reading attributes of type NF_STRING return an error code 56 -
4022!> Attempt to convert between text & numbers.
4023!------------------------------------------------------------------------------!
4024     SUBROUTINE get_attribute_string( id, attribute_name, value, global,       &
4025                                      variable_name )
4026
4027       USE pegrid
4028
4029       IMPLICIT NONE
4030
4031       CHARACTER(LEN=*)                ::  attribute_name   !< attribute name
4032       CHARACTER(LEN=*), OPTIONAL      ::  variable_name    !< variable name
4033       CHARACTER(LEN=*), INTENT(INOUT) ::  value            !< read value
4034
4035       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
4036       INTEGER(iwp)                ::  id_var           !< variable id
4037
4038       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
4039#if defined( __netcdf )
4040
4041!
4042!--    Read global attribute
4043       IF ( global )  THEN
4044          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
4045          CALL handle_error( 'get_attribute_string global', 525, attribute_name )
4046!
4047!--    Read attributes referring to a single variable. Therefore, first inquire
4048!--    variable id
4049       ELSE
4050          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4051          CALL handle_error( 'get_attribute_string', 525, attribute_name )
4052
4053          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
4054          CALL handle_error( 'get_attribute_string',525, attribute_name )
4055
4056       ENDIF
4057#endif
4058    END SUBROUTINE get_attribute_string
4059
4060
4061
4062!------------------------------------------------------------------------------!
4063! Description:
4064! ------------
4065!> Get dimension array for a given dimension
4066!------------------------------------------------------------------------------!
4067     SUBROUTINE get_dimension_length( id, dim_len, variable_name )
4068#if defined( __netcdf )
4069
4070       USE pegrid
4071
4072       IMPLICIT NONE
4073
4074       CHARACTER(LEN=*)            ::  variable_name    !< dimension name
4075       CHARACTER(LEN=100)          ::  dum              !< dummy variable to receive return character
4076
4077       INTEGER(iwp)                ::  dim_len          !< dimension size
4078       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
4079       INTEGER(iwp)                ::  id_dim           !< dimension id
4080
4081!
4082!--    First, inquire dimension ID
4083       nc_stat = NF90_INQ_DIMID( id, TRIM( variable_name ), id_dim )
4084       CALL handle_error( 'get_dimension_length', 526, variable_name )
4085!
4086!--    Inquire dimension length
4087       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim, dum, LEN = dim_len )
4088       CALL handle_error( 'get_dimension_length', 526, variable_name )
4089
4090#endif
4091    END SUBROUTINE get_dimension_length
4092
4093!------------------------------------------------------------------------------!
4094! Description:
4095! ------------
4096!> Reads a 1D integer variable from file.
4097!------------------------------------------------------------------------------!
4098     SUBROUTINE get_variable_1d_int( id, variable_name, var )
4099
4100       USE pegrid
4101
4102       IMPLICIT NONE
4103
4104       CHARACTER(LEN=*)            ::  variable_name    !< variable name
4105
4106       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
4107       INTEGER(iwp)                ::  id_var           !< dimension id
4108
4109       INTEGER(iwp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
4110#if defined( __netcdf )
4111
4112!
4113!--    First, inquire variable ID
4114       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4115       CALL handle_error( 'get_variable_1d_int', 527, variable_name )
4116!
4117!--    Inquire dimension length
4118       nc_stat = NF90_GET_VAR( id, id_var, var )
4119       CALL handle_error( 'get_variable_1d_int', 527, variable_name )
4120
4121#endif
4122    END SUBROUTINE get_variable_1d_int
4123
4124!------------------------------------------------------------------------------!
4125! Description:
4126! ------------
4127!> Reads a 1D float variable from file.
4128!------------------------------------------------------------------------------!
4129     SUBROUTINE get_variable_1d_real( id, variable_name, var )
4130
4131       USE pegrid
4132
4133       IMPLICIT NONE
4134
4135       CHARACTER(LEN=*)            ::  variable_name    !< variable name
4136
4137       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
4138       INTEGER(iwp)                ::  id_var           !< dimension id
4139
4140       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
4141#if defined( __netcdf )
4142
4143!
4144!--    First, inquire variable ID
4145       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4146       CALL handle_error( 'get_variable_1d_real', 528, variable_name )
4147!
4148!--    Inquire dimension length
4149       nc_stat = NF90_GET_VAR( id, id_var, var )
4150       CALL handle_error( 'get_variable_1d_real', 528, variable_name )
4151
4152#endif
4153    END SUBROUTINE get_variable_1d_real
4154
4155
4156!------------------------------------------------------------------------------!
4157! Description:
4158! ------------
4159!> Reads a time-dependent 1D float variable from file.
4160!------------------------------------------------------------------------------!
4161    SUBROUTINE get_variable_pr( id, variable_name, t, var )
4162#if defined( __netcdf )
4163
4164       USE pegrid
4165
4166       IMPLICIT NONE
4167
4168       CHARACTER(LEN=*)                      ::  variable_name    !< variable name
4169
4170       INTEGER(iwp), INTENT(IN)              ::  id               !< file id
4171       INTEGER(iwp), DIMENSION(1:2)          ::  id_dim           !< dimension ids
4172       INTEGER(iwp)                          ::  id_var           !< dimension id
4173       INTEGER(iwp)                          ::  n_file           !< number of data-points in file along z dimension
4174       INTEGER(iwp), INTENT(IN)              ::  t                !< timestep number
4175
4176       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
4177
4178!
4179!--    First, inquire variable ID
4180       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4181!
4182!--    Inquire dimension size of vertical dimension
4183       nc_stat = NF90_INQUIRE_VARIABLE( id, id_var, DIMIDS = id_dim )
4184       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim(1), LEN = n_file )
4185!
4186!--    Read variable.
4187       nc_stat = NF90_GET_VAR( id, id_var, var,                                &
4188                               start = (/ 1,      t     /),                    &
4189                               count = (/ n_file, 1     /) )
4190       CALL handle_error( 'get_variable_pr', 529, variable_name )
4191
4192#endif
4193    END SUBROUTINE get_variable_pr
4194
4195
4196!------------------------------------------------------------------------------!
4197! Description:
4198! ------------
4199!> Reads a 2D REAL variable from a file. Reading is done processor-wise,
4200!> i.e. each core reads its own domain in slices along x.
4201!------------------------------------------------------------------------------!
4202    SUBROUTINE get_variable_2d_real( id, variable_name, var, is, ie, js, je )
4203
4204       USE indices
4205       USE pegrid
4206
4207       IMPLICIT NONE
4208
4209       CHARACTER(LEN=*)              ::  variable_name   !< variable name
4210
4211       INTEGER(iwp)                  ::  i               !< running index along x direction
4212       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
4213       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
4214       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4215       INTEGER(iwp)                  ::  id_var          !< variable id
4216       INTEGER(iwp)                  ::  j               !< running index along y direction
4217       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
4218       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
4219       
4220       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  tmp   !< temporary variable to read data from file according
4221                                                         !< to its reverse memory access
4222       REAL(wp), DIMENSION(:,:), INTENT(INOUT) ::  var   !< variable to be read
4223#if defined( __netcdf )
4224!
4225!--    Inquire variable id
4226       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4227!
4228!--    Check for collective read-operation and set respective NetCDF flags if
4229!--    required.
4230       IF ( collective_read )  THEN
4231#if defined( __netcdf4_parallel )
4232          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4233#endif
4234       ENDIF
4235!
4236!--    Allocate temporary variable according to memory access on file.
4237       ALLOCATE( tmp(is:ie,js:je) )
4238!
4239!--    Get variable
4240       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
4241                               start = (/ is+1,      js+1 /),                  &
4242                               count = (/ ie-is + 1, je-js+1 /) )   
4243                               
4244       CALL handle_error( 'get_variable_2d_real', 530, variable_name )
4245!
4246!--    Resort data. Please note, dimension subscripts of var all start at 1.
4247       DO  i = is, ie 
4248          DO  j = js, je 
4249             var(j-js+1,i-is+1) = tmp(i,j)
4250          ENDDO
4251       ENDDO
4252       
4253       DEALLOCATE( tmp )
4254
4255#endif
4256    END SUBROUTINE get_variable_2d_real
4257
4258!------------------------------------------------------------------------------!
4259! Description:
4260! ------------
4261!> Reads a 2D 32-bit INTEGER variable from file. Reading is done processor-wise,
4262!> i.e. each core reads its own domain in slices along x.
4263!------------------------------------------------------------------------------!
4264    SUBROUTINE get_variable_2d_int32( id, variable_name, var, is, ie, js, je )
4265
4266       USE indices
4267       USE pegrid
4268
4269       IMPLICIT NONE
4270
4271       CHARACTER(LEN=*)              ::  variable_name   !< variable name
4272
4273       INTEGER(iwp)                  ::  i               !< running index along x direction
4274       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
4275       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
4276       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4277       INTEGER(iwp)                  ::  id_var          !< variable id
4278       INTEGER(iwp)                  ::  j               !< running index along y direction
4279       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
4280       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
4281       
4282       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
4283                                                            !< to its reverse memory access
4284       INTEGER(iwp), DIMENSION(:,:), INTENT(INOUT) ::  var  !< variable to be read
4285#if defined( __netcdf )
4286!
4287!--    Inquire variable id
4288       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4289!
4290!--    Check for collective read-operation and set respective NetCDF flags if
4291!--    required.
4292       IF ( collective_read )  THEN
4293#if defined( __netcdf4_parallel )       
4294          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4295#endif
4296       ENDIF
4297!
4298!--    Allocate temporary variable according to memory access on file.
4299       ALLOCATE( tmp(is:ie,js:je) )
4300!
4301!--    Get variable
4302       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
4303                               start = (/ is+1,      js+1 /),                  &
4304                               count = (/ ie-is + 1, je-js+1 /) )   
4305                               
4306       CALL handle_error( 'get_variable_2d_int32', 531, variable_name )                             
4307!
4308!--    Resort data. Please note, dimension subscripts of var all start at 1.
4309       DO  i = is, ie 
4310          DO  j = js, je 
4311             var(j-js+1,i-is+1) = tmp(i,j)
4312          ENDDO
4313       ENDDO
4314       
4315       DEALLOCATE( tmp )
4316
4317#endif
4318    END SUBROUTINE get_variable_2d_int32
4319
4320!------------------------------------------------------------------------------!
4321! Description:
4322! ------------
4323!> Reads a 2D 8-bit INTEGER variable from file. Reading is done processor-wise,
4324!> i.e. each core reads its own domain in slices along x.
4325!------------------------------------------------------------------------------!
4326    SUBROUTINE get_variable_2d_int8( id, variable_name, var, is, ie, js, je )
4327
4328       USE indices
4329       USE pegrid
4330
4331       IMPLICIT NONE
4332
4333       CHARACTER(LEN=*)              ::  variable_name   !< variable name
4334
4335       INTEGER(iwp)                  ::  i               !< running index along x direction
4336       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
4337       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
4338       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4339       INTEGER(iwp)                  ::  id_var          !< variable id
4340       INTEGER(iwp)                  ::  j               !< running index along y direction
4341       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
4342       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
4343       
4344       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
4345                                                               !< to its reverse memory access
4346       INTEGER(KIND=1), DIMENSION(:,:), INTENT(INOUT) ::  var  !< variable to be read
4347#if defined( __netcdf )
4348!
4349!--    Inquire variable id
4350       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4351!
4352!--    Check for collective read-operation and set respective NetCDF flags if
4353!--    required.
4354       IF ( collective_read )  THEN
4355#if defined( __netcdf4_parallel )       
4356          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4357#endif         
4358       ENDIF
4359!
4360!--    Allocate temporary variable according to memory access on file.
4361       ALLOCATE( tmp(is:ie,js:je) )
4362!
4363!--    Get variable
4364       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
4365                               start = (/ is+1,      js+1 /),                  &
4366                               count = (/ ie-is + 1, je-js+1 /) )   
4367                               
4368       CALL handle_error( 'get_variable_2d_int8', 532, variable_name )
4369!
4370!--    Resort data. Please note, dimension subscripts of var all start at 1.
4371       DO  i = is, ie 
4372          DO  j = js, je 
4373             var(j-js+1,i-is+1) = tmp(i,j)
4374          ENDDO
4375       ENDDO
4376       
4377       DEALLOCATE( tmp )
4378
4379#endif
4380    END SUBROUTINE get_variable_2d_int8
4381
4382
4383!------------------------------------------------------------------------------!
4384! Description:
4385! ------------
4386!> Reads a 3D 8-bit INTEGER variable from file.
4387!------------------------------------------------------------------------------!
4388    SUBROUTINE get_variable_3d_int8( id, variable_name, var, is, ie, js, je,   &
4389                                     ks, ke )
4390
4391       USE indices
4392       USE pegrid
4393
4394       IMPLICIT NONE
4395
4396       CHARACTER(LEN=*)              ::  variable_name   !< variable name
4397
4398       INTEGER(iwp)                  ::  i               !< index along x direction
4399       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
4400       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
4401       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4402       INTEGER(iwp)                  ::  id_var          !< variable id
4403       INTEGER(iwp)                  ::  j               !< index along y direction
4404       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
4405       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
4406       INTEGER(iwp)                  ::  k               !< index along any 3rd dimension
4407       INTEGER(iwp)                  ::  ke              !< start index of 3rd dimension
4408       INTEGER(iwp)                  ::  ks              !< end index of 3rd dimension
4409       
4410       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
4411                                                                 !< to its reverse memory access
4412
4413       INTEGER(KIND=1), DIMENSION(:,:,:), INTENT(INOUT) ::  var  !< variable to be read
4414#if defined( __netcdf )
4415
4416!
4417!--    Inquire variable id
4418       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )   
4419!
4420!--    Check for collective read-operation and set respective NetCDF flags if
4421!--    required.
4422       IF ( collective_read )  THEN
4423#if defined( __netcdf4_parallel )
4424          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4425#endif         
4426       ENDIF
4427!
4428!--    Allocate temporary variable according to memory access on file.
4429       ALLOCATE( tmp(is:ie,js:je,ks:ke) )
4430!
4431!--    Get variable
4432       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
4433                               start = (/ is+1,    js+1,    ks+1 /),           &
4434                               count = (/ ie-is+1, je-js+1, ke-ks+1 /) )                             
4435
4436       CALL handle_error( 'get_variable_3d_int8', 533, variable_name )                               
4437!
4438!--    Resort data. Please note, dimension subscripts of var all start at 1.
4439       DO  i = is, ie 
4440          DO  j = js, je
4441             DO  k = ks, ke
4442                var(k-ks+1,j-js+1,i-is+1) = tmp(i,j,k)
4443             ENDDO
4444          ENDDO
4445       ENDDO
4446       
4447       DEALLOCATE( tmp )
4448
4449#endif
4450    END SUBROUTINE get_variable_3d_int8
4451
4452
4453!------------------------------------------------------------------------------!
4454! Description:
4455! ------------
4456!> Reads a 3D float variable from file.
4457!------------------------------------------------------------------------------!
4458    SUBROUTINE get_variable_3d_real( id, variable_name, var, is, ie, js, je,   &
4459                                     ks, ke )
4460
4461       USE indices
4462       USE pegrid
4463
4464       IMPLICIT NONE
4465
4466       CHARACTER(LEN=*)              ::  variable_name   !< variable name
4467
4468       INTEGER(iwp)                  ::  i               !< index along x direction
4469       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
4470       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
4471       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4472       INTEGER(iwp)                  ::  id_var          !< variable id
4473       INTEGER(iwp)                  ::  j               !< index along y direction
4474       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
4475       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
4476       INTEGER(iwp)                  ::  k               !< index along any 3rd dimension
4477       INTEGER(iwp)                  ::  ke              !< start index of 3rd dimension
4478       INTEGER(iwp)                  ::  ks              !< end index of 3rd dimension
4479       
4480       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
4481                                                         !< to its reverse memory access
4482
4483       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var  !< variable to be read
4484#if defined( __netcdf )
4485
4486!
4487!--    Inquire variable id
4488       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 
4489!
4490!--    Check for collective read-operation and set respective NetCDF flags if
4491!--    required.
4492       IF ( collective_read )  THEN
4493#if defined( __netcdf4_parallel )       
4494          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4495#endif
4496       ENDIF
4497!
4498!--    Allocate temporary variable according to memory access on file.
4499       ALLOCATE( tmp(is:ie,js:je,ks:ke) )
4500!
4501!--    Get variable
4502       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
4503                               start = (/ is+1,    js+1,    ks+1 /),           &
4504                               count = (/ ie-is+1, je-js+1, ke-ks+1 /) )   
4505                               
4506       CALL handle_error( 'get_variable_3d_real', 534, variable_name )
4507!
4508!--    Resort data. Please note, dimension subscripts of var all start at 1.
4509       DO  i = is, ie 
4510          DO  j = js, je
4511             DO  k = ks, ke
4512                var(k-ks+1,j-js+1,i-is+1) = tmp(i,j,k)
4513             ENDDO
4514          ENDDO
4515       ENDDO
4516       
4517       DEALLOCATE( tmp )
4518
4519#endif
4520    END SUBROUTINE get_variable_3d_real
4521
4522!------------------------------------------------------------------------------!
4523! Description:
4524! ------------
4525!> Reads a 3D float array from file.
4526!------------------------------------------------------------------------------!
4527!     SUBROUTINE get_variable_3d_real_v( id, variable_name, is, ie, js, je, var )
4528!
4529!        USE indices
4530!        USE pegrid
4531!
4532!        IMPLICIT NONE
4533!
4534!        CHARACTER(LEN=*)              ::  variable_name   !< variable name
4535!
4536!        INTEGER(iwp), INTENT(IN)      ::  is,ie           !< index range along x direction
4537!        INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4538!        INTEGER(iwp)                  ::  id_var          !< variable id
4539!        INTEGER(iwp), INTENT(IN)      ::  js,je           !< index range along y direction
4540!        INTEGER(iwp)                  ::  n3              !< number of data-points along 3rd dimension
4541!
4542!        INTEGER(iwp)                  ::  i,j,k
4543!        INTEGER(iwp), DIMENSION(3)    ::  id_dim
4544!
4545!        REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var         !< variable to be read
4546! #if defined( __netcdf )
4547! !
4548! !--    Inside the ...static NetCDF files, the array is stored as float.
4549! !--    Therefore single precision is sufficiant for the temporary array
4550!
4551!        REAL(sp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_var     !< temporary array to read NetCDF data in i,j,k direction
4552!
4553! !kk    Please check, if it is time consuming to do the inquire every time
4554! !
4555! !--    Inquire variable id
4556!        nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4557! !
4558! !--    Get length of third dimension, required for the count parameter.
4559! !--    Therefore, first inquired dimension ids
4560!        nc_stat = NF90_INQUIRE_VARIABLE( id, id_var, DIMIDS = id_dim )
4561!        nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim(3), LEN = n3 )
4562!
4563! !
4564! !--    Check for collective read-operation and set respective NetCDF flags if
4565! !--    required.
4566!        IF ( collective_read )  THEN
4567! #if defined( __netcdf4_parallel )
4568!           nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4569! #endif
4570!        ENDIF
4571!
4572! !
4573! !--    Allocate temporary array ro read NetCDF data in i,j,k direction
4574!
4575!        ALLOCATE(tmp_var(is:ie,js:je,n3))
4576! !
4577! !--    Get variable
4578! !--    Read complete local 3-D array in oone call
4579!
4580!        nc_stat = NF90_GET_VAR( id, id_var, tmp_var,                            &
4581!                                start = (/ is+1, js+1, 1 /),                    &
4582!                                count = (/ ie-is+1, je-js+1, n3 /) )
4583!
4584!        CALL handle_error( 'get_variable_3d_real', 532 )
4585!
4586! !
4587! !--    Resort data in k,j,i direction
4588!
4589!        DO i=is,ie
4590!           DO j=js,je
4591!              DO K=1,n3
4592!                 var (k,j-js+1,i-is+1) = tmp_var(i,j,k)
4593!              END DO
4594!           END DO
4595!        END DO
4596!
4597!        DEALLOCATE(tmp_var)
4598!
4599! #endif
4600!     END SUBROUTINE get_variable_3d_real_v
4601
4602
4603!------------------------------------------------------------------------------!
4604! Description:
4605! ------------
4606!> Reads a 4D float variable from file.
4607!------------------------------------------------------------------------------!
4608    SUBROUTINE get_variable_4d_real( id, variable_name, var, is, ie, js, je,   &
4609                                     k1s, k1e, k2s, k2e )
4610
4611       USE indices
4612       USE pegrid
4613
4614       IMPLICIT NONE
4615
4616       CHARACTER(LEN=*)              ::  variable_name   !< variable name
4617
4618       INTEGER(iwp)                  ::  i               !< index along x direction
4619       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
4620       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
4621       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4622       INTEGER(iwp)                  ::  id_var          !< variable id
4623       INTEGER(iwp)                  ::  j               !< index along y direction
4624       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
4625       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
4626       INTEGER(iwp)                  ::  k1              !< index along 3rd direction
4627       INTEGER(iwp)                  ::  k1e             !< start index for 3rd dimension
4628       INTEGER(iwp)                  ::  k1s             !< end index for 3rd dimension
4629       INTEGER(iwp)                  ::  k2              !< index along 4th direction
4630       INTEGER(iwp)                  ::  k2e             !< start index for 4th dimension
4631       INTEGER(iwp)                  ::  k2s             !< end index for 4th dimension
4632
4633       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
4634                                                            !< to its reverse memory access
4635       REAL(wp), DIMENSION(:,:,:,:), INTENT(INOUT) ::  var  !< variable to be read
4636#if defined( __netcdf )
4637
4638!
4639!--    Inquire variable id
4640       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4641!
4642!--    Check for collective read-operation and set respective NetCDF flags if
4643!--    required.
4644       IF ( collective_read )  THEN
4645#if defined( __netcdf4_parallel )       
4646          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4647#endif
4648       ENDIF
4649!
4650!--    Allocate temporary variable according to memory access on file.
4651       ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e) )
4652!
4653!--    Get variable
4654       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
4655                               start = (/ is+1,    js+1,   k1s+1, k2s+1 /),    &
4656                               count = (/ ie-is+1, je-js+1,                    &
4657                                          k1e-k1s+1, k2e-k2s+1 /) )
4658
4659       CALL handle_error( 'get_variable_4d_real', 535, variable_name )
4660!
4661!--    Resort data. Please note, dimension subscripts of var all start at 1.
4662       DO  i = is, ie 
4663          DO  j = js, je
4664             DO  k1 = k1s, k1e
4665                DO  k2 = k2s, k2e
4666                   var(k2-k2s+1,k1-k1s+1,j-js+1,i-is+1) = tmp(i,j,k1,k2)
4667                ENDDO
4668             ENDDO
4669          ENDDO
4670       ENDDO
4671       
4672       DEALLOCATE( tmp )
4673#endif
4674    END SUBROUTINE get_variable_4d_real
4675
4676
4677
4678!------------------------------------------------------------------------------!
4679! Description:
4680! ------------
4681!> Reads a 3D float variables from dynamic driver, such as time-dependent xy-,
4682!> xz- or yz-boundary data as well as 3D initialization data. Please note,
4683!> the passed arguments are start indices and number of elements in each
4684!> dimension, which is in contrast to the other 3d versions where start- and
4685!> end indices are passed. The different handling of 3D dynamic variables is
4686!> due to its asymmetry for the u- and v component.
4687!------------------------------------------------------------------------------!
4688    SUBROUTINE get_variable_3d_real_dynamic( id, variable_name, var,           &
4689                                             i1s, i2s, i3s,                    &
4690                                             count_1, count_2, count_3,        &
4691                                             par_access )
4692                               
4693       USE indices
4694       USE pegrid
4695
4696       IMPLICIT NONE
4697
4698       CHARACTER(LEN=*)              ::  variable_name   !< variable name
4699
4700       LOGICAL                       ::  par_access      !< additional flag indicating whether parallel read operations should be performed or not
4701       
4702       INTEGER(iwp)                  ::  count_1         !< number of elements to be read along 1st dimension (with respect to file)
4703       INTEGER(iwp)                  ::  count_2         !< number of elements to be read along 2nd dimension (with respect to file)
4704       INTEGER(iwp)                  ::  count_3         !< number of elements to be read along 3rd dimension (with respect to file)
4705       INTEGER(iwp)                  ::  i1              !< running index along 1st dimension on file
4706       INTEGER(iwp)                  ::  i1s             !< start index for subdomain input along 1st dimension (with respect to file)
4707       INTEGER(iwp)                  ::  i2              !< running index along 2nd dimension on file       
4708       INTEGER(iwp)                  ::  i2s             !< start index for subdomain input along 2nd dimension (with respect to file)
4709       INTEGER(iwp)                  ::  i3              !< running index along 3rd dimension on file
4710       INTEGER(iwp)                  ::  i3s             !< start index of 3rd dimension, in dynamic file this is either time (2D boundary) or z (3D)
4711       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4712       INTEGER(iwp)                  ::  id_var          !< variable id
4713       INTEGER(iwp)                  ::  lb1             !< lower bound of 1st dimension (with respect to file)
4714       INTEGER(iwp)                  ::  lb2             !< lower bound of 2nd dimension (with respect to file)
4715       INTEGER(iwp)                  ::  lb3             !< lower bound of 3rd dimension (with respect to file)
4716       INTEGER(iwp)                  ::  ub1             !< upper bound of 1st dimension (with respect to file)
4717       INTEGER(iwp)                  ::  ub2             !< upper bound of 2nd dimension (with respect to file)
4718       INTEGER(iwp)                  ::  ub3             !< upper bound of 3rd dimension (with respect to file)
4719
4720       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
4721                                                         !< to its reverse memory access
4722       
4723       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var !< input variable
4724       
4725#if defined( __netcdf )
4726!
4727!--    Inquire variable id.
4728       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
4729!
4730!--    Check for collective read-operation and set respective NetCDF flags if
4731!--    required.
4732!--    Please note, in contrast to the other input routines where each PEs
4733!--    reads its subdomain data, dynamic input data not by all PEs, only
4734!--    by those which encompass lateral model boundaries. Hence, collective
4735!--    read operations are only enabled for top-boundary data.
4736       IF ( collective_read  .AND.  par_access )  THEN
4737#if defined( __netcdf4_parallel )       
4738          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
4739#endif
4740       ENDIF   
4741!
4742!--    Allocate temporary variable according to memory access on file.
4743!--    Therefore, determine dimension bounds of input array.
4744       lb1 = LBOUND(var,3)
4745       ub1 = UBOUND(var,3)
4746       lb2 = LBOUND(var,2)
4747       ub2 = UBOUND(var,2)
4748       lb3 = LBOUND(var,1)
4749       ub3 = UBOUND(var,1)
4750       ALLOCATE( tmp(lb1:ub1,lb2:ub2,lb3:ub3) )
4751!
4752!--    Get variable
4753       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
4754                               start = (/ i1s,     i2s,     i3s /),            &
4755                               count = (/ count_1, count_2, count_3 /) )
4756
4757       CALL handle_error( 'get_variable_3d_real_dynamic', 536, variable_name )
4758!
4759!--    Resort data. Please note, dimension subscripts of var all start at 1.
4760       DO  i3 = lb3, ub3
4761          DO i2 = lb2, ub2
4762             DO  i1 = lb1, ub1
4763                var(i3,i2,i1) = tmp(i1,i2,i3)
4764             ENDDO
4765          ENDDO
4766       ENDDO
4767       
4768       DEALLOCATE( tmp )       
4769#endif
4770    END SUBROUTINE get_variable_3d_real_dynamic
4771
4772
4773
4774!------------------------------------------------------------------------------!
4775! Description:
4776! ------------
4777!> Inquires the number of variables in a file
4778!------------------------------------------------------------------------------!
4779    SUBROUTINE inquire_num_variables( id, num_vars )
4780
4781       USE indices
4782       USE pegrid
4783
4784       IMPLICIT NONE
4785
4786       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
4787       INTEGER(iwp), INTENT(INOUT)   ::  num_vars        !< number of variables in a file
4788#if defined( __netcdf )
4789
4790       nc_stat = NF90_INQUIRE( id, NVARIABLES = num_vars )
4791       CALL handle_error( 'inquire_num_variables', 537 )
4792
4793#endif
4794    END SUBROUTINE inquire_num_variables
4795
4796
4797!------------------------------------------------------------------------------!
4798! Description:
4799! ------------
4800!> Inquires the variable names belonging to a file.
4801!------------------------------------------------------------------------------!
4802    SUBROUTINE inquire_variable_names( id, var_names )
4803
4804       USE indices
4805       USE pegrid
4806
4807       IMPLICIT NONE
4808
4809       CHARACTER(LEN=*), DIMENSION(:), INTENT(INOUT) ::  var_names   !< return variable - variable names
4810       INTEGER(iwp)                                  ::  i           !< loop variable
4811       INTEGER(iwp), INTENT(IN)                      ::  id          !< file id
4812       INTEGER(iwp)                                  ::  num_vars    !< number of variables (unused return parameter)
4813       INTEGER(iwp), DIMENSION(:), ALLOCATABLE       ::  varids      !< dummy array to strore variable ids temporarily
4814#if defined( __netcdf )
4815
4816       ALLOCATE( varids(1:SIZE(var_names)) )
4817       nc_stat = NF90_INQ_VARIDS( id, NVARS = num_vars, VARIDS = varids )
4818       CALL handle_error( 'inquire_variable_names', 538 )
4819
4820       DO  i = 1, SIZE(var_names)
4821          nc_stat = NF90_INQUIRE_VARIABLE( id, varids(i), NAME = var_names(i) )
4822          CALL handle_error( 'inquire_variable_names', 538 )
4823       ENDDO
4824
4825       DEALLOCATE( varids )
4826#endif
4827    END SUBROUTINE inquire_variable_names
4828
4829!------------------------------------------------------------------------------!
4830! Description:
4831! ------------
4832!> Prints out a text message corresponding to the current status.
4833!------------------------------------------------------------------------------!
4834    SUBROUTINE handle_error( routine_name, errno, name )
4835
4836       USE control_parameters,                                                 &
4837           ONLY:  message_string
4838
4839       IMPLICIT NONE
4840
4841       CHARACTER(LEN=6) ::  message_identifier
4842       CHARACTER(LEN=*) ::  routine_name
4843       CHARACTER(LEN=*), OPTIONAL ::  name
4844
4845       INTEGER(iwp) ::  errno
4846#if defined( __netcdf )
4847       
4848       IF ( nc_stat /= NF90_NOERR )  THEN
4849
4850          WRITE( message_identifier, '(''NC'',I4.4)' )  errno
4851         
4852          IF ( PRESENT( name ) )  THEN
4853             message_string = "Problem reading attribute/variable - " //       &
4854                              TRIM(name) // ": " //                            &
4855                              TRIM( NF90_STRERROR( nc_stat ) )
4856          ELSE
4857             message_string = TRIM( NF90_STRERROR( nc_stat ) )
4858          ENDIF
4859
4860          CALL message( routine_name, message_identifier, 2, 2, 0, 6, 1 )
4861
4862       ENDIF
4863
4864#endif
4865    END SUBROUTINE handle_error
4866
4867
4868 END MODULE netcdf_data_input_mod
Note: See TracBrowser for help on using the repository browser.