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

Last change on this file since 3246 was 3241, checked in by raasch, 6 years ago

various changes to avoid compiler warnings (mainly removal of unused variables)

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