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

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

Revise checks for relative surface fractions of vegetation, pavement and water surfaces

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