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

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

Remove unused variables from last commit

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