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

Last change on this file since 3516 was 3516, checked in by gronemeier, 6 years ago

bugfix: difference in z coordinate between file and PALM must be <1e-6; output of error 553 for all PEs (netcdf_data_input_mod)

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