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

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

Enable limitation of Obukhov length so that it does not become zero; to read input data from netcdf in init_3d_model use provided module variables instead of defining local ones; tests updated because changes in Obukhov lengths causes small differences during the initial phase of the run

  • Property svn:keywords set to Id
File size: 302.4 KB
Line 
1!> @file netcdf_data_input_mod.f90
2!------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the
6! terms of the GNU General Public License as published by the Free Software
7! Foundation, either version 3 of the License, or (at your option) any later
8! version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2019 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: netcdf_data_input_mod.f90 4186 2019-08-23 16:06:14Z suehring $
27! Minor formatting adjustments
28!
29! 4182 2019-08-22 15:20:23Z scharf
30! Corrected "Former revisions" section
31!
32! 4178 2019-08-21 11:13:06Z suehring
33! Implement input of external radiation forcing. Therefore, provide public
34! subroutines and variables.
35!
36! 4150 2019-08-08 20:00:47Z suehring
37! Some variables are given the public attribute, in order to call netcdf input
38! from single routines
39!
40! 4125 2019-07-29 13:31:44Z suehring
41! To enable netcdf-parallel access for lateral boundary data (dynamic input),
42! zero number of elements are passed to the respective get_variable routine
43! for non-boundary cores.
44!
45! 4100 2019-07-17 08:11:29Z forkel
46! Made check for input_pids_dynamic and 'inifor' more general
47!
48! 4012 2019-05-31 15:19:05Z monakurppa
49!
50! 3994 2019-05-22 18:08:09Z suehring
51! Remove single location message
52!
53! 3976 2019-05-15 11:02:34Z hellstea
54! Remove unused variables from last commit
55!
56! 3969 2019-05-13 12:14:33Z suehring
57! - clean-up index notations for emission_values to eliminate magic numbers
58! - introduce temporary variable dum_var_5d as well as subroutines
59!   get_var_5d_real and get_var_5d_real_dynamic
60! - remove emission-specific code in generic get_variable routines
61! - in subroutine netcdf_data_input_chemistry_data change netCDF LOD 1
62!   (default) emission_values to the following index order:
63!   z, y, x, species, category
64! - in subroutine netcdf_data_input_chemistry_data
65!   changed netCDF LOD 2 pre-processed emission_values to the following index
66!   order: time, z, y, x, species
67! - in type chem_emis_att_type replace nspec with n_emiss_species
68!   but retained nspec for backward compatibility with salsa_mod. (E.C. Chan)
69!
70! 3961 2019-05-08 16:12:31Z suehring
71! Revise checks for building IDs and types
72!
73! 3943 2019-05-02 09:50:41Z maronga
74! Temporarily disabled some (faulty) checks for static driver.
75!
76! 3942 2019-04-30 13:08:30Z kanani
77! Fix: increase LEN of all NetCDF attribute values (caused crash in
78! netcdf_create_global_atts due to insufficient length)
79!
80! 3941 2019-04-30 09:48:33Z suehring
81! Move check for grid dimension to an earlier point in time when first array
82! is read.
83! Improve checks for building types / IDs with respect to 2D/3D buildings.
84!
85! 3885 2019-04-11 11:29:34Z kanani
86! Changes related to global restructuring of location messages and introduction
87! of additional debug messages
88!
89! 3864 2019-04-05 09:01:56Z monakurppa
90! get_variable_4d_to_3d_real modified to enable read in data of type
91! data(t,y,x,n) one timestep at a time + some routines made public
92!
93! 3855 2019-04-03 10:00:59Z suehring
94! Typo removed
95!
96! 3854 2019-04-02 16:59:33Z suehring
97! Bugfix in one of the checks. Typo removed.
98!
99! 3744 2019-02-15 18:38:58Z suehring
100! Enable mesoscale offline nesting for chemistry variables as well as
101! initialization of chemistry via dynamic input file.
102!
103! 3705 2019-01-29 19:56:39Z suehring
104! Interface for attribute input of 8-bit and 32-bit integer
105!
106! 3704 2019-01-29 19:51:41Z suehring
107! unused variables removed
108!
109! 2696 2017-12-14 17:12:51Z kanani
110! Initial revision (suehring)
111!
112! Authors:
113! --------
114! @author Matthias Suehring
115! @author Edward C. Chan
116! @author Emanuele Russo
117!
118! Description:
119! ------------
120!> Modulue contains routines to input data according to Palm input data
121!> standart using dynamic and static input files.
122!> @todo - Chemistry: revise reading of netcdf file and ajdust formatting
123!>         according to standard!!! (ecc/done)
124!> @todo - Order input alphabetically
125!> @todo - Revise error messages and error numbers
126!> @todo - Input of missing quantities (chemical species, emission rates)
127!> @todo - Defninition and input of still missing variable attributes
128!>         (ecc/what are they?)
129!> @todo - Input of initial geostrophic wind profiles with cyclic conditions.
130!> @todo - remove z dimension from default_emission_data nad preproc_emission_data
131!          and correpsonding subroutines get_var_5d_real and get_var_5d_dynamic (ecc)
132!> @todo - decpreciate chem_emis_att_type@nspec (ecc)
133!> @todo - depreciate subroutines get_variable_4d_to_3d_real and
134!>         get_variable_5d_to_4d_real (ecc)
135!> @todo - introduce useful debug_message(s)
136!------------------------------------------------------------------------------!
137 MODULE netcdf_data_input_mod
138
139    USE control_parameters,                                                    &
140        ONLY:  coupling_char, io_blocks, io_group
141
142    USE cpulog,                                                                &
143        ONLY:  cpu_log, log_point_s
144
145    USE indices,                                                               &
146        ONLY:  nbgp
147
148    USE kinds
149
150#if defined ( __netcdf )
151    USE NETCDF
152#endif
153
154    USE pegrid
155
156    USE surface_mod,                                                           &
157        ONLY:  ind_pav_green, ind_veg_wall, ind_wat_win
158!
159!-- Define type for dimensions.
160    TYPE dims_xy
161       INTEGER(iwp) :: nx                             !< dimension length in x
162       INTEGER(iwp) :: ny                             !< dimension length in y
163       INTEGER(iwp) :: nz                             !< dimension length in z
164       REAL(wp), DIMENSION(:), ALLOCATABLE :: x       !< dimension array in x
165       REAL(wp), DIMENSION(:), ALLOCATABLE :: y       !< dimension array in y
166       REAL(wp), DIMENSION(:), ALLOCATABLE :: z       !< dimension array in z
167    END TYPE dims_xy
168!
169!-- Define data type for nesting in larger-scale models like COSMO.
170!-- Data type comprises u, v, w, pt, and q at lateral and top boundaries.
171    TYPE nest_offl_type
172
173       CHARACTER(LEN=16) ::  char_l = 'ls_forcing_left_'  !< leading substring for variables at left boundary
174       CHARACTER(LEN=17) ::  char_n = 'ls_forcing_north_' !< leading substring for variables at north boundary 
175       CHARACTER(LEN=17) ::  char_r = 'ls_forcing_right_' !< leading substring for variables at right boundary 
176       CHARACTER(LEN=17) ::  char_s = 'ls_forcing_south_' !< leading substring for variables at south boundary
177       CHARACTER(LEN=15) ::  char_t = 'ls_forcing_top_'   !< leading substring for variables at top boundary
178
179       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names         !< list of variable in dynamic input file
180       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_l  !< names of mesoscale nested chemistry variables at left boundary
181       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_n  !< names of mesoscale nested chemistry variables at north boundary
182       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_r  !< names of mesoscale nested chemistry variables at right boundary
183       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_s  !< names of mesoscale nested chemistry variables at south boundary
184       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem_t  !< names of mesoscale nested chemistry variables at top boundary
185
186       INTEGER(iwp) ::  nt     !< number of time levels in dynamic input file
187       INTEGER(iwp) ::  nzu    !< number of vertical levels on scalar grid in dynamic input file
188       INTEGER(iwp) ::  nzw    !< number of vertical levels on w grid in dynamic input file
189       INTEGER(iwp) ::  tind   !< time index for reference time in mesoscale-offline nesting
190       INTEGER(iwp) ::  tind_p !< time index for following time in mesoscale-offline nesting
191
192       LOGICAL      ::  init         = .FALSE. !< flag indicating that offline nesting is already initialized
193
194       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_l !< flags inidicating whether left boundary data for chemistry is in dynamic input file 
195       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_n !< flags inidicating whether north boundary data for chemistry is in dynamic input file
196       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_r !< flags inidicating whether right boundary data for chemistry is in dynamic input file
197       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_s !< flags inidicating whether south boundary data for chemistry is in dynamic input file
198       LOGICAL, DIMENSION(:), ALLOCATABLE ::  chem_from_file_t !< flags inidicating whether top boundary data for chemistry is in dynamic input file
199
200       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surface_pressure !< time dependent surface pressure
201       REAL(wp), DIMENSION(:), ALLOCATABLE ::  time             !< time levels in dynamic input file
202       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos         !< vertical levels at scalar grid in dynamic input file
203       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw_atmos         !< vertical levels at w grid in dynamic input file
204
205       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  ug         !< domain-averaged geostrophic component
206       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  vg         !< domain-averaged geostrophic component
207
208       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_left   !< u-component at left boundary
209       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_left   !< v-component at left boundary
210       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_left   !< w-component at left boundary
211       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_left   !< mixing ratio at left boundary
212       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_left  !< potentital temperautre at left boundary
213
214       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_north  !< u-component at north boundary
215       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_north  !< v-component at north boundary
216       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_north  !< w-component at north boundary
217       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_north  !< mixing ratio at north boundary
218       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_north !< potentital temperautre at north boundary
219
220       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_right  !< u-component at right boundary
221       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_right  !< v-component at right boundary
222       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_right  !< w-component at right boundary
223       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_right  !< mixing ratio at right boundary
224       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_right !< potentital temperautre at right boundary
225
226       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_south  !< u-component at south boundary
227       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_south  !< v-component at south boundary
228       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_south  !< w-component at south boundary
229       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_south  !< mixing ratio at south boundary
230       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_south !< potentital temperautre at south boundary
231
232       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  u_top    !< u-component at top boundary
233       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  v_top    !< v-component at top boundary
234       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  w_top    !< w-component at top boundary
235       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  q_top    !< mixing ratio at top boundary
236       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  pt_top   !< potentital temperautre at top boundary
237       
238       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_left   !< chemical species at left boundary
239       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_north  !< chemical species at left boundary
240       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_right  !< chemical species at left boundary
241       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_south  !< chemical species at left boundary
242       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  chem_top    !< chemical species at left boundary
243
244    END TYPE nest_offl_type
245
246    TYPE init_type
247
248       CHARACTER(LEN=16) ::  init_char = 'init_atmosphere_'          !< leading substring for init variables
249       CHARACTER(LEN=23) ::  origin_time = '2000-01-01 00:00:00 +00' !< reference time of input data
250       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names_chem !< list of chemistry variable names that can potentially be on file
251
252       INTEGER(iwp) ::  lod_msoil !< level of detail - soil moisture
253       INTEGER(iwp) ::  lod_pt    !< level of detail - pt
254       INTEGER(iwp) ::  lod_q     !< level of detail - q
255       INTEGER(iwp) ::  lod_tsoil !< level of detail - soil temperature
256       INTEGER(iwp) ::  lod_u     !< level of detail - u-component
257       INTEGER(iwp) ::  lod_v     !< level of detail - v-component
258       INTEGER(iwp) ::  lod_w     !< level of detail - w-component
259       INTEGER(iwp) ::  nx        !< number of scalar grid points along x in dynamic input file
260       INTEGER(iwp) ::  nxu       !< number of u grid points along x in dynamic input file
261       INTEGER(iwp) ::  ny        !< number of scalar grid points along y in dynamic input file
262       INTEGER(iwp) ::  nyv       !< number of v grid points along y in dynamic input file
263       INTEGER(iwp) ::  nzs       !< number of vertical soil levels in dynamic input file
264       INTEGER(iwp) ::  nzu       !< number of vertical levels on scalar grid in dynamic input file
265       INTEGER(iwp) ::  nzw       !< number of vertical levels on w grid in dynamic input file
266       
267       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  lod_chem !< level of detail - chemistry variables
268
269       LOGICAL ::  from_file_msoil  = .FALSE. !< flag indicating whether soil moisture is already initialized from file
270       LOGICAL ::  from_file_pt     = .FALSE. !< flag indicating whether pt is already initialized from file
271       LOGICAL ::  from_file_q      = .FALSE. !< flag indicating whether q is already initialized from file
272       LOGICAL ::  from_file_tsoil  = .FALSE. !< flag indicating whether soil temperature is already initialized from file
273       LOGICAL ::  from_file_u      = .FALSE. !< flag indicating whether u is already initialized from file
274       LOGICAL ::  from_file_ug     = .FALSE. !< flag indicating whether ug is already initialized from file
275       LOGICAL ::  from_file_v      = .FALSE. !< flag indicating whether v is already initialized from file
276       LOGICAL ::  from_file_vg     = .FALSE. !< flag indicating whether ug is already initialized from file
277       LOGICAL ::  from_file_w      = .FALSE. !< flag indicating whether w is already initialized from file
278       
279       LOGICAL, DIMENSION(:), ALLOCATABLE ::  from_file_chem !< flag indicating whether chemistry variable is read from file
280
281       REAL(wp) ::  fill_msoil              !< fill value for soil moisture
282       REAL(wp) ::  fill_pt                 !< fill value for pt
283       REAL(wp) ::  fill_q                  !< fill value for q
284       REAL(wp) ::  fill_tsoil              !< fill value for soil temperature
285       REAL(wp) ::  fill_u                  !< fill value for u
286       REAL(wp) ::  fill_v                  !< fill value for v
287       REAL(wp) ::  fill_w                  !< fill value for w
288       REAL(wp) ::  latitude = 0.0_wp       !< latitude of the lower left corner
289       REAL(wp) ::  longitude = 0.0_wp      !< longitude of the lower left corner
290       REAL(wp) ::  origin_x = 500000.0_wp  !< UTM easting of the lower left corner
291       REAL(wp) ::  origin_y = 0.0_wp       !< UTM northing of the lower left corner
292       REAL(wp) ::  origin_z = 0.0_wp       !< reference height of input data
293       REAL(wp) ::  rotation_angle = 0.0_wp !< rotation angle of input data
294
295       REAL(wp), DIMENSION(:), ALLOCATABLE ::  fill_chem    !< fill value - chemistry variables
296       REAL(wp), DIMENSION(:), ALLOCATABLE ::  msoil_1d     !< initial vertical profile of soil moisture
297       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init      !< initial vertical profile of pt
298       REAL(wp), DIMENSION(:), ALLOCATABLE ::  q_init       !< initial vertical profile of q
299       REAL(wp), DIMENSION(:), ALLOCATABLE ::  tsoil_1d     !< initial vertical profile of soil temperature
300       REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_init       !< initial vertical profile of u
301       REAL(wp), DIMENSION(:), ALLOCATABLE ::  ug_init      !< initial vertical profile of ug
302       REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_init       !< initial vertical profile of v
303       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vg_init      !< initial vertical profile of ug
304       REAL(wp), DIMENSION(:), ALLOCATABLE ::  w_init       !< initial vertical profile of w
305       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z_soil       !< vertical levels in soil in dynamic input file, used for interpolation
306       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zu_atmos     !< vertical levels at scalar grid in dynamic input file, used for interpolation
307       REAL(wp), DIMENSION(:), ALLOCATABLE ::  zw_atmos     !< vertical levels at w grid in dynamic input file, used for interpolation
308       
309       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  chem_init  !< initial vertical profiles of chemistry variables
310
311
312       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  msoil_3d !< initial 3d soil moisture provide by Inifor and interpolated onto soil grid
313       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  tsoil_3d !< initial 3d soil temperature provide by Inifor and interpolated onto soil grid
314
315    END TYPE init_type
316
317!-- Data type for the general information of chemistry emissions, do not dependent on the particular chemical species
318    TYPE chem_emis_att_type 
319
320       !-DIMENSIONS
321       
322       INTEGER(iwp)                                 :: nspec=0            !< no of chem species provided in emission_values
323       INTEGER(iwp)                                 :: n_emiss_species=0  !< no of chem species provided in emission_values
324                                                                          !< same function as nspec, which will be depreciated (ecc)
325                                                                                 
326       INTEGER(iwp)                                 :: ncat=0             !< number of emission categories
327       INTEGER(iwp)                                 :: nvoc=0             !< number of VOC components
328       INTEGER(iwp)                                 :: npm=0              !< number of PM components
329       INTEGER(iwp)                                 :: nnox=2             !< number of NOx components: NO and NO2
330       INTEGER(iwp)                                 :: nsox=2             !< number of SOX components: SO and SO4
331       INTEGER(iwp)                                 :: nhoursyear         !< number of hours of a specific year in the HOURLY mode
332                                                                          !< of the default mode
333       INTEGER(iwp)                                 :: nmonthdayhour      !< number of month days and hours in the MDH mode
334                                                                          !< of the default mode
335       INTEGER(iwp)                                 :: dt_emission        !< Number of emissions timesteps for one year
336                                                                          !< in the pre-processed emissions case
337       !-- 1d emission input variables
338       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: pm_name       !< Names of PM components
339       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: cat_name      !< Emission category names
340       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: species_name  !< Names of emission chemical species
341       CHARACTER (LEN=25),ALLOCATABLE, DIMENSION(:) :: voc_name      !< Names of VOCs components
342       CHARACTER (LEN=25)                           :: units         !< Units
343
344       INTEGER(iwp)                                 :: i_hour         !< indices for assigning emission values at different timesteps
345       INTEGER(iwp),ALLOCATABLE, DIMENSION(:)       :: cat_index      !< Indices for emission categories
346       INTEGER(iwp),ALLOCATABLE, DIMENSION(:)       :: species_index  !< Indices for emission chem species
347
348       REAL(wp),ALLOCATABLE, DIMENSION(:)           :: xm             !< Molecular masses of emission chem species
349
350       !-- 2d emission input variables
351       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: hourly_emis_time_factor  !< Time factors for HOURLY emissions (DEFAULT mode)
352       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: mdh_emis_time_factor     !< Time factors for MDH emissions (DEFAULT mode)
353       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: nox_comp                 !< Composition of NO and NO2
354       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: sox_comp                 !< Composition of SO2 and SO4
355       REAL(wp),ALLOCATABLE, DIMENSION(:,:)         :: voc_comp                 !< Composition of VOC components (not fixed)
356
357       !-- 3d emission input variables
358       REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)       :: pm_comp                  !< Composition of PM components (not fixed)
359 
360    END TYPE chem_emis_att_type
361
362
363!-- Data type for the values of chemistry emissions
364    TYPE chem_emis_val_type 
365
366       !REAL(wp),ALLOCATABLE, DIMENSION(:,:)     :: stack_height           !< stack height (ecc / to be implemented)
367       REAL(wp),ALLOCATABLE, DIMENSION(:,:,:)    :: default_emission_data  !< Emission input values for LOD1 (DEFAULT mode)
368       REAL(wp),ALLOCATABLE, DIMENSION(:,:,:,:)  :: preproc_emission_data  !< Emission input values for LOD2 (PRE-PROCESSED mode)
369
370    END TYPE chem_emis_val_type
371
372!
373!-- Define data structures for different input data types.
374!-- 8-bit Integer 2D
375    TYPE int_2d_8bit
376       INTEGER(KIND=1) ::  fill = -127                      !< fill value
377       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE ::  var !< respective variable
378
379       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
380    END TYPE int_2d_8bit
381!
382!-- 8-bit Integer 3D
383    TYPE int_3d_8bit
384       INTEGER(KIND=1) ::  fill = -127                           !< fill value
385       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d !< respective variable
386
387       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
388    END TYPE int_3d_8bit
389!
390!-- 32-bit Integer 2D
391    TYPE int_2d_32bit
392       INTEGER(iwp) ::  fill = -9999                      !< fill value
393       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  var  !< respective variable
394
395       LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used
396    END TYPE int_2d_32bit
397!
398!-- Define data type to read 1D real variables
399    TYPE real_1d
400       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
401
402       REAL(wp) ::  fill = -9999.9_wp                  !< fill value
403       
404       REAL(wp), DIMENSION(:), ALLOCATABLE ::  var     !< respective variable
405    END TYPE real_1d   
406!
407!-- Define data type to read 2D real variables
408    TYPE real_2d
409       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
410
411       REAL(wp) ::  fill = -9999.9_wp                !< fill value
412       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var !< respective variable
413    END TYPE real_2d
414
415!
416!-- Define data type to read 3D real variables
417    TYPE real_3d
418       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
419
420       INTEGER(iwp) ::  nz   !< number of grid points along vertical dimension
421
422       REAL(wp) ::  fill = -9999.9_wp                  !< fill value
423       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  var !< respective variable
424    END TYPE real_3d
425!
426!-- Define data structure where the dimension and type of the input depends
427!-- on the given level of detail.
428!-- For buildings, the input is either 2D float, or 3d byte.
429    TYPE build_in
430       INTEGER(iwp)    ::  lod = 1                               !< level of detail
431       INTEGER(KIND=1) ::  fill2 = -127                          !< fill value for lod = 2
432       INTEGER(iwp)    ::  nz                                    !< number of vertical layers in file
433       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d !< 3d variable (lod = 2)
434
435       REAL(wp), DIMENSION(:), ALLOCATABLE ::  z                 !< vertical coordinate for 3D building, used for consistency check
436
437       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
438
439       REAL(wp)                              ::  fill1 = -9999.9_wp !< fill values for lod = 1
440       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  var_2d             !< 2d variable (lod = 1)
441    END TYPE build_in
442
443!
444!-- For soil_type, the input is either 2D or 3D one-byte integer.
445    TYPE soil_in
446       INTEGER(iwp)                                   ::  lod = 1      !< level of detail
447       INTEGER(KIND=1)                                ::  fill = -127  !< fill value for lod = 2
448       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE   ::  var_2d       !< 2d variable (lod = 1)
449       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_3d       !< 3d variable (lod = 2)
450
451       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
452    END TYPE soil_in
453
454!
455!-- Define data type for fractions between surface types
456    TYPE fracs
457       INTEGER(iwp)                            ::  nf             !< total number of fractions
458       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  nfracs         !< dimension array for fraction
459
460       LOGICAL ::  from_file = .FALSE. !< flag indicating whether an input variable is available and read from file or default values are used
461
462       REAL(wp)                                ::  fill = -9999.9_wp !< fill value
463       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  frac              !< respective fraction between different surface types
464    END TYPE fracs
465!
466!-- Data type for parameter lists, Depending on the given level of detail,
467!-- the input is 3D or 4D
468    TYPE pars
469       INTEGER(iwp)                            ::  lod = 1         !< level of detail
470       INTEGER(iwp)                            ::  np              !< total number of parameters
471       INTEGER(iwp)                            ::  nz              !< vertical dimension - number of soil layers
472       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  layers          !< dimension array for soil layers
473       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  pars            !< dimension array for parameters
474
475       LOGICAL ::  from_file = .FALSE.  !< flag indicating whether an input variable is available and read from file or default values are used
476
477       REAL(wp)                                  ::  fill = -9999.9_wp !< fill value
478       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  pars_xy           !< respective parameters, level of detail = 1
479       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  pars_xyz          !< respective parameters, level of detail = 2
480    END TYPE pars
481!
482!-- Define type for global file attributes
483!-- Please refer to the PALM data standard for a detailed description of each
484!-- attribute.
485    TYPE global_atts_type
486       CHARACTER(LEN=200) ::  acronym = ' '                      !< acronym of institution
487       CHARACTER(LEN=7)   ::  acronym_char = 'acronym'           !< name of attribute
488       CHARACTER(LEN=200) ::  author  = ' '                      !< first name, last name, email adress
489       CHARACTER(LEN=6)   ::  author_char = 'author'             !< name of attribute
490       CHARACTER(LEN=200) ::  campaign = 'PALM-4U'               !< name of campaign
491       CHARACTER(LEN=8)   ::  campaign_char = 'campaign'         !< name of attribute
492       CHARACTER(LEN=200) ::  comment = ' '                      !< comment to data
493       CHARACTER(LEN=7)   ::  comment_char = 'comment'           !< name of attribute
494       CHARACTER(LEN=200) ::  contact_person = ' '               !< first name, last name, email adress
495       CHARACTER(LEN=14)  ::  contact_person_char = 'contact_person'  !< name of attribute
496       CHARACTER(LEN=200) ::  conventions = 'CF-1.7'             !< netCDF convention
497       CHARACTER(LEN=11)  ::  conventions_char = 'Conventions'   !< name of attribute
498       CHARACTER(LEN=23 ) ::  creation_time = ' '                !< creation time of data set
499       CHARACTER(LEN=13)  ::  creation_time_char = 'creation_time'  !< name of attribute
500       CHARACTER(LEN=200) ::  data_content = ' '                 !< content of data set
501       CHARACTER(LEN=12)  ::  data_content_char = 'data_content' !< name of attribute
502       CHARACTER(LEN=200) ::  dependencies = ' '                 !< dependencies of data set
503       CHARACTER(LEN=12)  ::  dependencies_char = 'dependencies' !< name of attribute
504       CHARACTER(LEN=200) ::  history = ' '                      !< information about data processing
505       CHARACTER(LEN=7)   ::  history_char = 'history'           !< name of attribute
506       CHARACTER(LEN=200) ::  institution = ' '                  !< name of responsible institution
507       CHARACTER(LEN=11)  ::  institution_char = 'institution'   !< name of attribute
508       CHARACTER(LEN=200) ::  keywords = ' '                     !< keywords of data set
509       CHARACTER(LEN=8)   ::  keywords_char = 'keywords'         !< name of attribute
510       CHARACTER(LEN=200) ::  licence = ' '                      !< licence of data set
511       CHARACTER(LEN=7)   ::  licence_char = 'licence'           !< name of attribute
512       CHARACTER(LEN=200) ::  location = ' '                     !< place which refers to data set
513       CHARACTER(LEN=8)   ::  location_char = 'location'         !< name of attribute
514       CHARACTER(LEN=10)  ::  origin_lat_char = 'origin_lat'     !< name of attribute
515       CHARACTER(LEN=10)  ::  origin_lon_char = 'origin_lon'     !< name of attribute
516       CHARACTER(LEN=23 ) ::  origin_time = '2000-01-01 00:00:00 +00'  !< reference time
517       CHARACTER(LEN=11)  ::  origin_time_char = 'origin_time'   !< name of attribute
518       CHARACTER(LEN=8)   ::  origin_x_char = 'origin_x'         !< name of attribute
519       CHARACTER(LEN=8)   ::  origin_y_char = 'origin_y'         !< name of attribute
520       CHARACTER(LEN=8)   ::  origin_z_char = 'origin_z'         !< name of attribute
521       CHARACTER(LEN=12)  ::  palm_version_char = 'palm_version' !< name of attribute
522       CHARACTER(LEN=200) ::  references = ' '                   !< literature referring to data set
523       CHARACTER(LEN=10)  ::  references_char = 'references'     !< name of attribute
524       CHARACTER(LEN=14)  ::  rotation_angle_char = 'rotation_angle'  !< name of attribute
525       CHARACTER(LEN=200) ::  site = ' '                         !< name of model domain
526       CHARACTER(LEN=4)   ::  site_char = 'site'                 !< name of attribute
527       CHARACTER(LEN=200) ::  source = ' '                       !< source of data set
528       CHARACTER(LEN=6)   ::  source_char = 'source'             !< name of attribute
529       CHARACTER(LEN=200) ::  title = ' '                        !< title of data set
530       CHARACTER(LEN=5)   ::  title_char = 'title'               !< name of attribute
531       CHARACTER(LEN=7)   ::  version_char = 'version'           !< name of attribute
532
533       INTEGER(iwp) ::  version              !< version of data set
534
535       REAL(wp) ::  origin_lat               !< latitude of lower left corner
536       REAL(wp) ::  origin_lon               !< longitude of lower left corner
537       REAL(wp) ::  origin_x                 !< easting (UTM coordinate) of lower left corner
538       REAL(wp) ::  origin_y                 !< northing (UTM coordinate) of lower left corner
539       REAL(wp) ::  origin_z                 !< reference height
540       REAL(wp) ::  palm_version             !< PALM version of data set
541       REAL(wp) ::  rotation_angle           !< rotation angle of coordinate system of data set
542    END TYPE global_atts_type
543!
544!-- Define type for coordinate reference system (crs)
545    TYPE crs_type
546       CHARACTER(LEN=200) ::  epsg_code = 'EPSG:25831'                   !< EPSG code
547       CHARACTER(LEN=200) ::  grid_mapping_name = 'transverse_mercator'  !< name of grid mapping
548       CHARACTER(LEN=200) ::  long_name = 'coordinate reference system'  !< name of variable crs
549       CHARACTER(LEN=200) ::  units = 'm'                                !< unit of crs
550
551       REAL(wp) ::  false_easting = 500000.0_wp                  !< false easting
552       REAL(wp) ::  false_northing = 0.0_wp                      !< false northing
553       REAL(wp) ::  inverse_flattening = 298.257223563_wp        !< 1/f (default for WGS84)
554       REAL(wp) ::  latitude_of_projection_origin = 0.0_wp       !< latitude of projection origin
555       REAL(wp) ::  longitude_of_central_meridian = 3.0_wp       !< longitude of central meridian of UTM zone (default: zone 31)
556       REAL(wp) ::  longitude_of_prime_meridian = 0.0_wp         !< longitude of prime meridian
557       REAL(wp) ::  scale_factor_at_central_meridian = 0.9996_wp !< scale factor of UTM coordinates
558       REAL(wp) ::  semi_major_axis = 6378137.0_wp               !< length of semi major axis (default for WGS84)
559    END TYPE crs_type
560
561!
562!-- Define variables
563    TYPE(crs_type)   ::  coord_ref_sys  !< coordinate reference system
564
565    TYPE(dims_xy)    ::  dim_static     !< data structure for x, y-dimension in static input file
566
567    TYPE(nest_offl_type) ::  nest_offl  !< data structure for data input at lateral and top boundaries (provided by Inifor) 
568
569    TYPE(init_type) ::  init_3d    !< data structure for the initialization of the 3D flow and soil fields
570    TYPE(init_type) ::  init_model !< data structure for the initialization of the model
571
572!
573!-- Define 2D variables of type NC_BYTE
574    TYPE(int_2d_8bit)  ::  albedo_type_f     !< input variable for albedo type
575    TYPE(int_2d_8bit)  ::  building_type_f   !< input variable for building type
576    TYPE(int_2d_8bit)  ::  pavement_type_f   !< input variable for pavenment type
577    TYPE(int_2d_8bit)  ::  street_crossing_f !< input variable for water type
578    TYPE(int_2d_8bit)  ::  street_type_f     !< input variable for water type
579    TYPE(int_2d_8bit)  ::  vegetation_type_f !< input variable for vegetation type
580    TYPE(int_2d_8bit)  ::  water_type_f      !< input variable for water type
581!
582!-- Define 3D variables of type NC_BYTE
583    TYPE(int_3d_8bit)  ::  building_obstruction_f    !< input variable for building obstruction
584    TYPE(int_3d_8bit)  ::  building_obstruction_full !< input variable for building obstruction
585!
586!-- Define 2D variables of type NC_INT
587    TYPE(int_2d_32bit) ::  building_id_f     !< input variable for building ID
588!
589!-- Define 2D variables of type NC_FLOAT
590    TYPE(real_2d) ::  terrain_height_f       !< input variable for terrain height
591    TYPE(real_2d) ::  uvem_irradiance_f      !< input variable for uvem irradiance lookup table
592    TYPE(real_2d) ::  uvem_integration_f     !< input variable for uvem integration
593!
594!-- Define 3D variables of type NC_FLOAT
595    TYPE(real_3d) ::  basal_area_density_f    !< input variable for basal area density - resolved vegetation
596    TYPE(real_3d) ::  leaf_area_density_f     !< input variable for leaf area density - resolved vegetation
597    TYPE(real_3d) ::  root_area_density_lad_f !< input variable for root area density - resolved vegetation
598    TYPE(real_3d) ::  root_area_density_lsm_f !< input variable for root area density - parametrized vegetation
599    TYPE(real_3d) ::  uvem_radiance_f         !< input variable for uvem radiance lookup table
600    TYPE(real_3d) ::  uvem_projarea_f         !< input variable for uvem projection area lookup table
601!
602!-- Define input variable for buildings
603    TYPE(build_in) ::  buildings_f           !< input variable for buildings
604!
605!-- Define input variables for soil_type
606    TYPE(soil_in)  ::  soil_type_f           !< input variable for soil type
607
608    TYPE(fracs) ::  surface_fraction_f       !< input variable for surface fraction
609
610    TYPE(pars)  ::  albedo_pars_f              !< input variable for albedo parameters
611    TYPE(pars)  ::  building_pars_f            !< input variable for building parameters
612    TYPE(pars)  ::  pavement_pars_f            !< input variable for pavement parameters
613    TYPE(pars)  ::  pavement_subsurface_pars_f !< input variable for pavement parameters
614    TYPE(pars)  ::  soil_pars_f                !< input variable for soil parameters
615    TYPE(pars)  ::  vegetation_pars_f          !< input variable for vegetation parameters
616    TYPE(pars)  ::  water_pars_f               !< input variable for water parameters
617
618    TYPE(chem_emis_att_type)                             ::  chem_emis_att    !< Input Information of Chemistry Emission Data from netcdf 
619    TYPE(chem_emis_val_type), ALLOCATABLE, DIMENSION(:)  ::  chem_emis        !< Input Chemistry Emission Data from netcdf 
620
621    CHARACTER(LEN=3)  ::  char_lod  = 'lod'         !< name of level-of-detail attribute in NetCDF file
622
623    CHARACTER(LEN=10) ::  char_fill = '_FillValue'        !< name of fill value attribute in NetCDF file
624
625    CHARACTER(LEN=100) ::  input_file_static  = 'PIDS_STATIC'  !< Name of file which comprises static input data
626    CHARACTER(LEN=100) ::  input_file_dynamic = 'PIDS_DYNAMIC' !< Name of file which comprises dynamic input data
627    CHARACTER(LEN=100) ::  input_file_chem    = 'PIDS_CHEM'    !< Name of file which comprises chemistry input data
628    CHARACTER(LEN=100) ::  input_file_uvem    = 'PIDS_UVEM'    !< Name of file which comprises static uv_exposure model input data
629    CHARACTER(LEN=100) ::  input_file_vm      = 'PIDS_VM'      !< Name of file which comprises virtual measurement data
630   
631    CHARACTER(LEN=25), ALLOCATABLE, DIMENSION(:) ::  string_values  !< output of string variables read from netcdf input files
632    CHARACTER(LEN=50), DIMENSION(:), ALLOCATABLE ::  vars_pids      !< variable in input file
633
634    INTEGER(iwp)                                     ::  id_emis        !< NetCDF id of input file for chemistry emissions: TBD: It has to be removed
635
636    INTEGER(iwp) ::  nc_stat         !< return value of nf90 function call
637    INTEGER(iwp) ::  num_var_pids    !< number of variables in file
638    INTEGER(iwp) ::  pids_id         !< file id
639
640    LOGICAL ::  input_pids_static  = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing static information exists
641    LOGICAL ::  input_pids_dynamic = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing dynamic information exists
642    LOGICAL ::  input_pids_chem    = .FALSE.   !< Flag indicating whether Palm-input-data-standard file containing chemistry information exists
643    LOGICAL ::  input_pids_uvem    = .FALSE.   !< Flag indicating whether uv-expoure-model input file containing static information exists
644    LOGICAL ::  input_pids_vm      = .FALSE.   !< Flag indicating whether input file for virtual measurements exist
645
646    LOGICAL ::  collective_read = .FALSE.      !< Enable NetCDF collective read
647
648    TYPE(global_atts_type) ::  input_file_atts !< global attributes of input file
649
650    SAVE
651
652    PRIVATE
653
654    INTERFACE netcdf_data_input_interpolate
655       MODULE PROCEDURE netcdf_data_input_interpolate_1d
656       MODULE PROCEDURE netcdf_data_input_interpolate_1d_soil
657       MODULE PROCEDURE netcdf_data_input_interpolate_2d
658       MODULE PROCEDURE netcdf_data_input_interpolate_3d
659    END INTERFACE netcdf_data_input_interpolate
660
661    INTERFACE netcdf_data_input_check_dynamic
662       MODULE PROCEDURE netcdf_data_input_check_dynamic
663    END INTERFACE netcdf_data_input_check_dynamic
664
665    INTERFACE netcdf_data_input_check_static
666       MODULE PROCEDURE netcdf_data_input_check_static
667    END INTERFACE netcdf_data_input_check_static
668
669    INTERFACE netcdf_data_input_chemistry_data                       
670       MODULE PROCEDURE netcdf_data_input_chemistry_data
671    END INTERFACE netcdf_data_input_chemistry_data
672   
673    INTERFACE netcdf_data_input_get_dimension_length                       
674       MODULE PROCEDURE netcdf_data_input_get_dimension_length
675    END INTERFACE netcdf_data_input_get_dimension_length
676
677    INTERFACE netcdf_data_input_inquire_file
678       MODULE PROCEDURE netcdf_data_input_inquire_file
679    END INTERFACE netcdf_data_input_inquire_file
680
681    INTERFACE netcdf_data_input_init
682       MODULE PROCEDURE netcdf_data_input_init
683    END INTERFACE netcdf_data_input_init
684   
685    INTERFACE netcdf_data_input_att
686       MODULE PROCEDURE netcdf_data_input_att_int8
687       MODULE PROCEDURE netcdf_data_input_att_int32
688       MODULE PROCEDURE netcdf_data_input_att_real
689       MODULE PROCEDURE netcdf_data_input_att_string
690    END INTERFACE netcdf_data_input_att
691
692    INTERFACE netcdf_data_input_init_3d
693       MODULE PROCEDURE netcdf_data_input_init_3d
694    END INTERFACE netcdf_data_input_init_3d
695   
696    INTERFACE netcdf_data_input_init_lsm
697       MODULE PROCEDURE netcdf_data_input_init_lsm
698    END INTERFACE netcdf_data_input_init_lsm
699
700    INTERFACE netcdf_data_input_offline_nesting
701       MODULE PROCEDURE netcdf_data_input_offline_nesting
702    END INTERFACE netcdf_data_input_offline_nesting
703
704    INTERFACE netcdf_data_input_surface_data
705       MODULE PROCEDURE netcdf_data_input_surface_data
706    END INTERFACE netcdf_data_input_surface_data
707
708    INTERFACE netcdf_data_input_var
709       MODULE PROCEDURE netcdf_data_input_var_char
710       MODULE PROCEDURE netcdf_data_input_var_real_1d
711       MODULE PROCEDURE netcdf_data_input_var_real_2d
712    END INTERFACE netcdf_data_input_var
713
714    INTERFACE netcdf_data_input_uvem
715       MODULE PROCEDURE netcdf_data_input_uvem
716    END INTERFACE netcdf_data_input_uvem
717
718    INTERFACE get_variable
719       MODULE PROCEDURE get_variable_1d_char
720       MODULE PROCEDURE get_variable_1d_int
721       MODULE PROCEDURE get_variable_1d_real
722       MODULE PROCEDURE get_variable_2d_int8
723       MODULE PROCEDURE get_variable_2d_int32
724       MODULE PROCEDURE get_variable_2d_real
725       MODULE PROCEDURE get_variable_3d_int8
726       MODULE PROCEDURE get_variable_3d_real
727       MODULE PROCEDURE get_variable_3d_real_dynamic
728       MODULE PROCEDURE get_variable_4d_to_3d_real
729       MODULE PROCEDURE get_variable_4d_real
730       MODULE PROCEDURE get_variable_5d_to_4d_real
731       MODULE PROCEDURE get_variable_5d_real           ! (ecc) temp subroutine 4 reading 5D NC arrays
732       MODULE PROCEDURE get_variable_5d_real_dynamic   ! 2B removed as z is out of emission_values
733       MODULE PROCEDURE get_variable_string
734    END INTERFACE get_variable
735
736    INTERFACE get_variable_pr
737       MODULE PROCEDURE get_variable_pr
738    END INTERFACE get_variable_pr
739
740    INTERFACE get_attribute
741       MODULE PROCEDURE get_attribute_real
742       MODULE PROCEDURE get_attribute_int8
743       MODULE PROCEDURE get_attribute_int32
744       MODULE PROCEDURE get_attribute_string
745    END INTERFACE get_attribute
746
747!
748!-- Public data structures
749    PUBLIC real_1d,                                                            &
750           real_2d
751!
752!-- Public variables
753    PUBLIC albedo_pars_f, albedo_type_f, basal_area_density_f, buildings_f,    &
754           building_id_f, building_pars_f, building_type_f, char_fill,         &
755           chem_emis, chem_emis_att, chem_emis_att_type, chem_emis_val_type,   &
756           coord_ref_sys,                                                      &
757           init_3d, init_model, input_file_atts,                               &
758           input_file_dynamic,                                                 &
759           input_file_static,                                                  &
760           input_pids_static,                                                  &
761           input_pids_dynamic, input_pids_vm, input_file_vm,                   &
762           leaf_area_density_f, nest_offl,                                     &
763           num_var_pids,                                                       &
764           pavement_pars_f, pavement_subsurface_pars_f, pavement_type_f,       &
765           pids_id,                                                            &
766           root_area_density_lad_f, root_area_density_lsm_f, soil_pars_f,      &
767           soil_type_f, street_crossing_f, street_type_f, surface_fraction_f,  &
768           terrain_height_f, vegetation_pars_f, vegetation_type_f,             &
769           vars_pids,                                                          &
770           water_pars_f, water_type_f
771!
772!-- Public uv exposure variables
773    PUBLIC building_obstruction_f, input_file_uvem, input_pids_uvem,           &
774           netcdf_data_input_uvem,                                             &
775           uvem_integration_f, uvem_irradiance_f,                              &
776           uvem_projarea_f, uvem_radiance_f
777
778!
779!-- Public subroutines
780    PUBLIC netcdf_data_input_check_dynamic, netcdf_data_input_check_static,    &
781           netcdf_data_input_chemistry_data,                                   &
782           netcdf_data_input_get_dimension_length,                             &
783           netcdf_data_input_inquire_file,                                     &
784           netcdf_data_input_init, netcdf_data_input_init_lsm,                 &
785           netcdf_data_input_init_3d, netcdf_data_input_att,                   &
786           netcdf_data_input_interpolate, netcdf_data_input_offline_nesting,   &
787           netcdf_data_input_surface_data, netcdf_data_input_topo,             &
788           netcdf_data_input_var, get_attribute, get_variable, open_read_file, &
789           check_existence, inquire_num_variables, inquire_variable_names,     &
790           close_input_file
791
792
793 CONTAINS
794
795!------------------------------------------------------------------------------!
796! Description:
797! ------------
798!> Inquires whether NetCDF input files according to Palm-input-data standard
799!> exist. Moreover, basic checks are performed.
800!------------------------------------------------------------------------------!
801    SUBROUTINE netcdf_data_input_inquire_file
802
803       USE control_parameters,                                                 &
804           ONLY:  topo_no_distinct
805
806       IMPLICIT NONE
807
808#if defined ( __netcdf )
809       INQUIRE( FILE = TRIM( input_file_static )   // TRIM( coupling_char ),   &
810                EXIST = input_pids_static  )
811       INQUIRE( FILE = TRIM( input_file_dynamic ) // TRIM( coupling_char ),    &
812                EXIST = input_pids_dynamic )
813       INQUIRE( FILE = TRIM( input_file_chem )    // TRIM( coupling_char ),    &
814                EXIST = input_pids_chem )
815       INQUIRE( FILE = TRIM( input_file_uvem ) // TRIM( coupling_char ),       &
816                EXIST = input_pids_uvem  )
817       INQUIRE( FILE = TRIM( input_file_vm )      // TRIM( coupling_char ),    &
818                EXIST = input_pids_vm )
819#endif
820
821!
822!--    As long as topography can be input via ASCII format, no distinction
823!--    between building and terrain can be made. This case, classify all
824!--    surfaces as default type. Same in case land-surface and urban-surface
825!--    model are not applied.
826       IF ( .NOT. input_pids_static )  THEN
827          topo_no_distinct = .TRUE.
828       ENDIF
829
830    END SUBROUTINE netcdf_data_input_inquire_file
831
832!------------------------------------------------------------------------------!
833! Description:
834! ------------
835!> Reads global attributes and coordinate reference system required for
836!> initialization of the model.
837!------------------------------------------------------------------------------!
838    SUBROUTINE netcdf_data_input_init
839
840       IMPLICIT NONE
841
842       INTEGER(iwp) ::  id_mod     !< NetCDF id of input file
843       INTEGER(iwp) ::  var_id_crs !< NetCDF id of variable crs
844
845       IF ( .NOT. input_pids_static )  RETURN
846
847#if defined ( __netcdf )
848!
849!--    Open file in read-only mode
850       CALL open_read_file( TRIM( input_file_static ) //                       &
851                            TRIM( coupling_char ), id_mod )
852!
853!--    Read global attributes
854       CALL get_attribute( id_mod, input_file_atts%origin_lat_char,            &
855                           input_file_atts%origin_lat, .TRUE. )
856
857       CALL get_attribute( id_mod, input_file_atts%origin_lon_char,            &
858                           input_file_atts%origin_lon, .TRUE. )
859
860       CALL get_attribute( id_mod, input_file_atts%origin_time_char,           &
861                           input_file_atts%origin_time, .TRUE. )
862
863       CALL get_attribute( id_mod, input_file_atts%origin_x_char,              &
864                           input_file_atts%origin_x, .TRUE. )
865
866       CALL get_attribute( id_mod, input_file_atts%origin_y_char,              &
867                           input_file_atts%origin_y, .TRUE. )
868
869       CALL get_attribute( id_mod, input_file_atts%origin_z_char,              &
870                           input_file_atts%origin_z, .TRUE. )
871
872       CALL get_attribute( id_mod, input_file_atts%rotation_angle_char,        &
873                           input_file_atts%rotation_angle, .TRUE. )
874
875       CALL get_attribute( id_mod, input_file_atts%author_char,                &
876                           input_file_atts%author, .TRUE., no_abort=.FALSE. )
877       CALL get_attribute( id_mod, input_file_atts%contact_person_char,        &
878                           input_file_atts%contact_person, .TRUE., no_abort=.FALSE. )
879       CALL get_attribute( id_mod, input_file_atts%institution_char,           &
880                           input_file_atts%institution,    .TRUE., no_abort=.FALSE. )
881       CALL get_attribute( id_mod, input_file_atts%acronym_char,               &
882                           input_file_atts%acronym,        .TRUE., no_abort=.FALSE. )
883
884       CALL get_attribute( id_mod, input_file_atts%campaign_char,              &
885                           input_file_atts%campaign, .TRUE., no_abort=.FALSE. )
886       CALL get_attribute( id_mod, input_file_atts%location_char,              &
887                           input_file_atts%location, .TRUE., no_abort=.FALSE. )
888       CALL get_attribute( id_mod, input_file_atts%site_char,                  &
889                           input_file_atts%site,     .TRUE., no_abort=.FALSE. )
890
891       CALL get_attribute( id_mod, input_file_atts%source_char,                &
892                           input_file_atts%source,     .TRUE., no_abort=.FALSE. )
893       CALL get_attribute( id_mod, input_file_atts%references_char,            &
894                           input_file_atts%references, .TRUE., no_abort=.FALSE. )
895       CALL get_attribute( id_mod, input_file_atts%keywords_char,              &
896                           input_file_atts%keywords,   .TRUE., no_abort=.FALSE. )
897       CALL get_attribute( id_mod, input_file_atts%licence_char,               &
898                           input_file_atts%licence,    .TRUE., no_abort=.FALSE. )
899       CALL get_attribute( id_mod, input_file_atts%comment_char,               &
900                           input_file_atts%comment,    .TRUE., no_abort=.FALSE. )
901!
902!--    Read coordinate reference system if available
903       nc_stat = NF90_INQ_VARID( id_mod, 'crs', var_id_crs )
904       IF ( nc_stat == NF90_NOERR )  THEN
905          CALL get_attribute( id_mod, 'epsg_code',                             &
906                              coord_ref_sys%epsg_code,                         &
907                              .FALSE., 'crs' )
908          CALL get_attribute( id_mod, 'false_easting',                         &
909                              coord_ref_sys%false_easting,                     &
910                              .FALSE., 'crs' )
911          CALL get_attribute( id_mod, 'false_northing',                        &
912                              coord_ref_sys%false_northing,                    &
913                              .FALSE., 'crs' )
914          CALL get_attribute( id_mod, 'grid_mapping_name',                     &
915                              coord_ref_sys%grid_mapping_name,                 &
916                              .FALSE., 'crs' )
917          CALL get_attribute( id_mod, 'inverse_flattening',                    &
918                              coord_ref_sys%inverse_flattening,                &
919                              .FALSE., 'crs' )
920          CALL get_attribute( id_mod, 'latitude_of_projection_origin',         &
921                              coord_ref_sys%latitude_of_projection_origin,     &
922                              .FALSE., 'crs' )
923          CALL get_attribute( id_mod, 'long_name',                             &
924                              coord_ref_sys%long_name,                         &
925                              .FALSE., 'crs' )
926          CALL get_attribute( id_mod, 'longitude_of_central_meridian',         &
927                              coord_ref_sys%longitude_of_central_meridian,     &
928                              .FALSE., 'crs' )
929          CALL get_attribute( id_mod, 'longitude_of_prime_meridian',           &
930                              coord_ref_sys%longitude_of_prime_meridian,       &
931                              .FALSE., 'crs' )
932          CALL get_attribute( id_mod, 'scale_factor_at_central_meridian',      &
933                              coord_ref_sys%scale_factor_at_central_meridian,  &
934                              .FALSE., 'crs' )
935          CALL get_attribute( id_mod, 'semi_major_axis',                       &
936                              coord_ref_sys%semi_major_axis,                   &
937                              .FALSE., 'crs' )
938          CALL get_attribute( id_mod, 'units',                                 &
939                              coord_ref_sys%units,                             &
940                              .FALSE., 'crs' )
941       ELSE
942!
943!--       Calculate central meridian from origin_lon
944          coord_ref_sys%longitude_of_central_meridian = &
945             CEILING( input_file_atts%origin_lon / 6.0_wp ) * 6.0_wp - 3.0_wp
946       ENDIF
947!
948!--    Finally, close input file
949       CALL close_input_file( id_mod )
950#endif
951!
952!--    Copy latitude, longitude, origin_z, rotation angle on init type
953       init_model%latitude        = input_file_atts%origin_lat
954       init_model%longitude       = input_file_atts%origin_lon
955       init_model%origin_time     = input_file_atts%origin_time 
956       init_model%origin_x        = input_file_atts%origin_x
957       init_model%origin_y        = input_file_atts%origin_y
958       init_model%origin_z        = input_file_atts%origin_z 
959       init_model%rotation_angle  = input_file_atts%rotation_angle 
960           
961!
962!--    In case of nested runs, each model domain might have different longitude
963!--    and latitude, which would result in different Coriolis parameters and
964!--    sun-zenith angles. To avoid this, longitude and latitude in each model
965!--    domain will be set to the values of the root model. Please note, this
966!--    synchronization is required already here.
967#if defined( __parallel )
968       CALL MPI_BCAST( init_model%latitude,  1, MPI_REAL, 0,                   &
969                       MPI_COMM_WORLD, ierr )
970       CALL MPI_BCAST( init_model%longitude, 1, MPI_REAL, 0,                   &
971                       MPI_COMM_WORLD, ierr )
972#endif
973
974    END SUBROUTINE netcdf_data_input_init
975   
976!------------------------------------------------------------------------------!
977! Description:
978! ------------
979!> Read an array of characters.
980!------------------------------------------------------------------------------!
981    SUBROUTINE netcdf_data_input_var_char( val, search_string, id_mod )
982
983       IMPLICIT NONE
984
985       CHARACTER(LEN=*) ::  search_string     !< name of the variable
986       CHARACTER(LEN=*), DIMENSION(:) ::  val !< variable which should be read
987       
988       INTEGER(iwp) ::  id_mod   !< NetCDF id of input file
989
990#if defined ( __netcdf )
991!
992!--    Read variable
993       CALL get_variable( id_mod, search_string, val )
994#endif           
995
996    END SUBROUTINE netcdf_data_input_var_char
997   
998!------------------------------------------------------------------------------!
999! Description:
1000! ------------
1001!> Read an 1D array of REAL values.
1002!------------------------------------------------------------------------------!
1003    SUBROUTINE netcdf_data_input_var_real_1d( val, search_string, id_mod )
1004
1005       IMPLICIT NONE
1006
1007       CHARACTER(LEN=*) ::  search_string     !< name of the variable     
1008       
1009       INTEGER(iwp) ::  id_mod        !< NetCDF id of input file
1010       
1011       REAL(wp), DIMENSION(:) ::  val !< variable which should be read
1012
1013#if defined ( __netcdf )
1014!
1015!--    Read variable
1016       CALL get_variable( id_mod, search_string, val )
1017#endif           
1018
1019    END SUBROUTINE netcdf_data_input_var_real_1d
1020   
1021!------------------------------------------------------------------------------!
1022! Description:
1023! ------------
1024!> Read an 1D array of REAL values.
1025!------------------------------------------------------------------------------!
1026    SUBROUTINE netcdf_data_input_var_real_2d( val, search_string,              &
1027                                              id_mod, d1s, d1e, d2s, d2e )
1028
1029       IMPLICIT NONE
1030
1031       CHARACTER(LEN=*) ::  search_string     !< name of the variable     
1032       
1033       INTEGER(iwp) ::  id_mod  !< NetCDF id of input file
1034       INTEGER(iwp) ::  d1e     !< end index of first dimension to be read
1035       INTEGER(iwp) ::  d2e     !< end index of second dimension to be read
1036       INTEGER(iwp) ::  d1s     !< start index of first dimension to be read
1037       INTEGER(iwp) ::  d2s     !< start index of second dimension to be read
1038       
1039       REAL(wp), DIMENSION(:,:) ::  val !< variable which should be read
1040
1041#if defined ( __netcdf )
1042!
1043!--    Read character variable
1044       CALL get_variable( id_mod, search_string, val, d1s, d1e, d2s, d2e )
1045#endif           
1046
1047    END SUBROUTINE netcdf_data_input_var_real_2d
1048   
1049!------------------------------------------------------------------------------!
1050! Description:
1051! ------------
1052!> Read a global string attribute
1053!------------------------------------------------------------------------------!
1054    SUBROUTINE netcdf_data_input_att_string( val, search_string, id_mod,       &
1055                                             input_file, global, openclose,    &
1056                                             variable_name )
1057
1058       IMPLICIT NONE
1059
1060       CHARACTER(LEN=*) ::  search_string !< name of the attribue
1061       CHARACTER(LEN=*) ::  val           !< attribute
1062       
1063       CHARACTER(LEN=*) ::  input_file    !< name of input file
1064       CHARACTER(LEN=*) ::  openclose     !< string indicating whether NetCDF needs to be opend or closed
1065       CHARACTER(LEN=*) ::  variable_name !< string indicating whether NetCDF needs to be opend or closed 
1066       
1067       INTEGER(iwp) ::  id_mod   !< NetCDF id of input file
1068       
1069       LOGICAL ::  global                 !< flag indicating a global or a variable's attribute
1070
1071#if defined ( __netcdf )
1072!
1073!--    Open file in read-only mode if necessary
1074       IF ( openclose == 'open' )  THEN
1075          CALL open_read_file( TRIM( input_file ) // TRIM( coupling_char ), &
1076                                  id_mod )
1077       ENDIF
1078!
1079!--    Read global attribute
1080       IF ( global )  THEN
1081          CALL get_attribute( id_mod, search_string, val, global )
1082!
1083!--    Read variable attribute
1084       ELSE
1085          CALL get_attribute( id_mod, search_string, val, global, variable_name )
1086       ENDIF
1087!
1088!--    Close input file
1089       IF ( openclose == 'close' )  CALL close_input_file( id_mod )
1090#endif           
1091
1092    END SUBROUTINE netcdf_data_input_att_string
1093   
1094!------------------------------------------------------------------------------!
1095! Description:
1096! ------------
1097!> Read a global 8-bit integer attribute
1098!------------------------------------------------------------------------------!
1099    SUBROUTINE netcdf_data_input_att_int8( val, search_string, id_mod,         &
1100                                           input_file, global, openclose,      &
1101                                           variable_name )
1102
1103       IMPLICIT NONE
1104
1105       CHARACTER(LEN=*) ::  search_string !< name of the attribue
1106       
1107       CHARACTER(LEN=*) ::  input_file    !< name of input file
1108       CHARACTER(LEN=*) ::  openclose     !< string indicating whether NetCDF needs to be opend or closed
1109       CHARACTER(LEN=*) ::  variable_name !< string indicating whether NetCDF needs to be opend or closed
1110       
1111       INTEGER(iwp) ::  id_mod   !< NetCDF id of input file
1112       INTEGER(KIND=1) ::  val      !< value of the attribute
1113       
1114       LOGICAL ::  global        !< flag indicating a global or a variable's attribute
1115
1116#if defined ( __netcdf )
1117!
1118!--    Open file in read-only mode
1119       IF ( openclose == 'open' )  THEN
1120          CALL open_read_file( TRIM( input_file ) // TRIM( coupling_char ), &
1121                                  id_mod )
1122       ENDIF
1123!
1124!--    Read global attribute
1125       IF ( global )  THEN
1126          CALL get_attribute( id_mod, search_string, val, global )
1127!
1128!--    Read variable attribute
1129       ELSE
1130          CALL get_attribute( id_mod, search_string, val, global, variable_name )
1131       ENDIF
1132!
1133!--    Finally, close input file
1134       IF ( openclose == 'close' )  CALL close_input_file( id_mod )
1135#endif           
1136
1137    END SUBROUTINE netcdf_data_input_att_int8
1138   
1139!------------------------------------------------------------------------------!
1140! Description:
1141! ------------
1142!> Read a global 32-bit integer attribute
1143!------------------------------------------------------------------------------!
1144    SUBROUTINE netcdf_data_input_att_int32( val, search_string, id_mod,        &
1145                                            input_file, global, openclose,     &
1146                                            variable_name )
1147
1148       IMPLICIT NONE
1149
1150       CHARACTER(LEN=*) ::  search_string !< name of the attribue
1151       
1152       CHARACTER(LEN=*) ::  input_file    !< name of input file
1153       CHARACTER(LEN=*) ::  openclose     !< string indicating whether NetCDF needs to be opend or closed
1154       CHARACTER(LEN=*) ::  variable_name !< string indicating whether NetCDF needs to be opend or closed
1155       
1156       INTEGER(iwp) ::  id_mod   !< NetCDF id of input file
1157       INTEGER(iwp) ::  val      !< value of the attribute
1158       
1159       LOGICAL ::  global        !< flag indicating a global or a variable's attribute
1160
1161#if defined ( __netcdf )
1162!
1163!--    Open file in read-only mode
1164       IF ( openclose == 'open' )  THEN
1165          CALL open_read_file( TRIM( input_file ) // TRIM( coupling_char ), &
1166                                  id_mod )
1167       ENDIF
1168!
1169!--    Read global attribute
1170       IF ( global )  THEN
1171          CALL get_attribute( id_mod, search_string, val, global )
1172!
1173!--    Read variable attribute
1174       ELSE
1175          CALL get_attribute( id_mod, search_string, val, global, variable_name )
1176       ENDIF
1177!
1178!--    Finally, close input file
1179       IF ( openclose == 'close' )  CALL close_input_file( id_mod )
1180#endif           
1181
1182    END SUBROUTINE netcdf_data_input_att_int32
1183   
1184!------------------------------------------------------------------------------!
1185! Description:
1186! ------------
1187!> Read a global real attribute
1188!------------------------------------------------------------------------------!
1189    SUBROUTINE netcdf_data_input_att_real( val, search_string, id_mod,         &
1190                                           input_file, global, openclose,      &
1191                                           variable_name )
1192
1193       IMPLICIT NONE
1194
1195       CHARACTER(LEN=*) ::  search_string !< name of the attribue
1196       
1197       CHARACTER(LEN=*) ::  input_file    !< name of input file
1198       CHARACTER(LEN=*) ::  openclose     !< string indicating whether NetCDF needs to be opend or closed
1199       CHARACTER(LEN=*) ::  variable_name !< string indicating whether NetCDF needs to be opend or closed
1200       
1201       INTEGER(iwp) ::  id_mod            !< NetCDF id of input file
1202       
1203       LOGICAL ::  global                 !< flag indicating a global or a variable's attribute
1204       
1205       REAL(wp) ::  val                   !< value of the attribute
1206
1207#if defined ( __netcdf )
1208!
1209!--    Open file in read-only mode
1210       IF ( openclose == 'open' )  THEN
1211          CALL open_read_file( TRIM( input_file ) // TRIM( coupling_char ), &
1212                                  id_mod )
1213       ENDIF
1214!
1215!--    Read global attribute
1216       IF ( global )  THEN
1217          CALL get_attribute( id_mod, search_string, val, global )
1218!
1219!--    Read variable attribute
1220       ELSE
1221          CALL get_attribute( id_mod, search_string, val, global, variable_name )
1222       ENDIF
1223!
1224!--    Finally, close input file
1225       IF ( openclose == 'close' )  CALL close_input_file( id_mod )
1226#endif           
1227
1228    END SUBROUTINE netcdf_data_input_att_real
1229
1230!------------------------------------------------------------------------------!
1231! Description:
1232! ------------
1233!> Reads Chemistry NETCDF Input data, such as emission values, emission species, etc.
1234!------------------------------------------------------------------------------!
1235
1236    SUBROUTINE netcdf_data_input_chemistry_data(emt_att,emt)
1237
1238       USE chem_modules,                                       &
1239           ONLY:  emiss_lod, time_fac_type, surface_csflux_name
1240
1241       USE control_parameters,                                 &
1242           ONLY:  message_string
1243
1244       USE indices,                                            &
1245           ONLY:  nxl, nxr, nys, nyn
1246
1247       IMPLICIT NONE
1248
1249       TYPE(chem_emis_att_type), INTENT(INOUT)                             ::  emt_att
1250       TYPE(chem_emis_val_type), ALLOCATABLE, DIMENSION(:), INTENT(INOUT)  ::  emt
1251   
1252       INTEGER(iwp)  ::  i, j, k      !< generic counters
1253       INTEGER(iwp)  ::  ispec        !< index for number of emission species in input
1254       INTEGER(iwp)  ::  len_dims     !< Length of dimension
1255       INTEGER(iwp)  ::  num_vars     !< number of variables in netcdf input file
1256
1257!
1258!-- dum_var_4d are designed to read in emission_values from the chemistry netCDF file.
1259!-- Currently the vestigial "z" dimension in emission_values makes it a 5D array,
1260!-- hence the corresponding dum_var_5d array.  When the "z" dimension is removed
1261!-- completely, dum_var_4d will be used instead
1262!-- (ecc 20190425)
1263
1264!       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:)    ::  dum_var_4d  !< temp array 4 4D chem emission data
1265       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:,:)  ::  dum_var_5d  !< temp array 4 5D chem emission data
1266
1267!
1268!-- Start processing data
1269!
1270!-- Emission LOD 0 (Parameterized mode)
1271
1272        IF  ( emiss_lod == 0 )  THEN
1273
1274! for reference (ecc)
1275!       IF (TRIM(mode_emis) == "PARAMETERIZED" .OR. TRIM(mode_emis) == "parameterized") THEN
1276
1277           ispec=1
1278           emt_att%n_emiss_species = 0
1279
1280!
1281!-- number of species
1282
1283           DO  WHILE (TRIM( surface_csflux_name( ispec ) ) /= 'novalue' )
1284
1285             emt_att%n_emiss_species = emt_att%n_emiss_species + 1
1286             ispec=ispec+1
1287!
1288!-- followling line retained for compatibility with salsa_mod
1289!-- which still uses emt_att%nspec heavily (ecc)
1290
1291             emt_att%nspec = emt_att%nspec + 1
1292
1293           ENDDO
1294
1295!
1296!-- allocate emission values data type arrays
1297
1298          ALLOCATE ( emt(emt_att%n_emiss_species) )
1299
1300!
1301!-- Read EMISSION SPECIES NAMES
1302
1303!
1304!-- allocate space for strings
1305
1306          ALLOCATE (emt_att%species_name(emt_att%n_emiss_species) )
1307 
1308         DO ispec = 1, emt_att%n_emiss_species
1309            emt_att%species_name(ispec) = TRIM(surface_csflux_name(ispec))
1310         ENDDO
1311
1312!
1313!-- LOD 1 (default mode) and LOD 2 (pre-processed mode)
1314
1315       ELSE
1316
1317#if defined ( __netcdf )
1318
1319          IF ( .NOT. input_pids_chem )  RETURN
1320
1321!
1322!-- first we allocate memory space for the emission species and then
1323!-- we differentiate between LOD 1 (default mode) and LOD 2 (pre-processed mode)
1324
1325!
1326!-- open emission data file ( {palmcase}_chemistry )
1327
1328          CALL open_read_file ( TRIM(input_file_chem) // TRIM(coupling_char), id_emis )
1329
1330!
1331!-- inquire number of variables
1332
1333          CALL inquire_num_variables ( id_emis, num_vars )
1334
1335!
1336!-- Get General Dimension Lengths: only # species and # categories.
1337!-- Tther dimensions depend on the emission mode or specific components
1338
1339          CALL netcdf_data_input_get_dimension_length (    &
1340                                 id_emis, emt_att%n_emiss_species, 'nspecies' )
1341
1342!
1343!-- backward compatibility for salsa_mod (ecc)
1344
1345          emt_att%nspec = emt_att%n_emiss_species
1346
1347!
1348!-- Allocate emission values data type arrays
1349
1350          ALLOCATE ( emt(emt_att%n_emiss_species) )
1351
1352!
1353!-- READING IN SPECIES NAMES
1354
1355!
1356!-- Allocate memory for species names
1357
1358          ALLOCATE ( emt_att%species_name(emt_att%n_emiss_species) )
1359
1360!
1361!-- Retrieve variable name (again, should use n_emiss_strlen)
1362
1363          CALL get_variable( id_emis, 'emission_name',    &
1364                             string_values, emt_att%n_emiss_species )
1365          emt_att%species_name=string_values
1366
1367!
1368!-- dealocate string_values previously allocated in get_variable call
1369
1370          IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)
1371
1372!
1373!-- READING IN SPECIES INDICES
1374
1375!
1376!-- Allocate memory for species indices
1377
1378          ALLOCATE ( emt_att%species_index(emt_att%n_emiss_species) )
1379
1380!
1381!-- Retrieve variable data
1382
1383          CALL get_variable( id_emis, 'emission_index', emt_att%species_index )
1384!
1385!-- Now the routine has to distinguish between chemistry emission
1386!-- LOD 1 (DEFAULT mode) and LOD 2 (PRE-PROCESSED mode)
1387
1388!
1389!-- START OF EMISSION LOD 1 (DEFAULT MODE)
1390
1391
1392          IF  ( emiss_lod == 1 )  THEN
1393
1394! for reference (ecc)
1395!          IF (TRIM(mode_emis) == "DEFAULT" .OR. TRIM(mode_emis) == "default") THEN
1396
1397!
1398!-- get number of emission categories
1399
1400             CALL netcdf_data_input_get_dimension_length (           &
1401                                    id_emis, emt_att%ncat, 'ncat' )
1402
1403!-- READING IN EMISSION CATEGORIES INDICES
1404
1405             ALLOCATE ( emt_att%cat_index(emt_att%ncat) )
1406
1407!
1408!-- Retrieve variable data
1409
1410             CALL get_variable( id_emis, 'emission_cat_index', emt_att%cat_index )
1411
1412
1413!
1414!-- Loop through individual species to get basic information on
1415!-- VOC/PM/NOX/SOX
1416
1417!------------------------------------------------------------------------------
1418!-- NOTE - CHECK ARRAY INDICES FOR READING IN NAMES AND SPECIES
1419!--        IN LOD1 (DEFAULT MODE) FOR THE VARIOUS MODE SPLITS
1420!--        AS ALL ID_EMIS CONDITIONALS HAVE BEEN REMOVED FROM GET_VAR
1421!--        FUNCTIONS.  IN THEORY THIS WOULD MEAN ALL ARRAYS SHOULD BE
1422!--        READ FROM 0 to N-1 (C CONVENTION) AS OPPOSED TO 1 to N
1423!--        (FORTRAN CONVENTION).  KEEP THIS IN MIND !!
1424!--        (ecc 20190424)
1425!------------------------------------------------------------------------------
1426 
1427             DO  ispec = 1, emt_att%n_emiss_species
1428
1429!
1430!-- VOC DATA (name and composition)
1431
1432                IF  ( TRIM(emt_att%species_name(ispec)) == "VOC" .OR.                  &
1433                      TRIM(emt_att%species_name(ispec)) == "voc" )  THEN
1434
1435!
1436!-- VOC name
1437                   CALL netcdf_data_input_get_dimension_length (     &
1438                                          id_emis, emt_att%nvoc, 'nvoc' )
1439                   ALLOCATE ( emt_att%voc_name(emt_att%nvoc) )
1440                   CALL get_variable ( id_emis,"emission_voc_name",  &
1441                                       string_values, emt_att%nvoc )
1442                   emt_att%voc_name = string_values
1443                   IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)
1444
1445!
1446!-- VOC composition
1447
1448                   ALLOCATE ( emt_att%voc_comp(emt_att%ncat,emt_att%nvoc) )
1449                   CALL get_variable ( id_emis, "composition_voc", emt_att%voc_comp,     &
1450                                       1, emt_att%ncat, 1, emt_att%nvoc )
1451
1452                ENDIF  ! VOC
1453
1454!
1455!-- PM DATA (name and composition)
1456
1457                IF  ( TRIM(emt_att%species_name(ispec)) == "PM" .OR.                   &
1458                      TRIM(emt_att%species_name(ispec)) == "pm")  THEN
1459
1460!
1461!-- PM name
1462
1463                   CALL netcdf_data_input_get_dimension_length (     &
1464                                          id_emis, emt_att%npm, 'npm' )
1465                   ALLOCATE ( emt_att%pm_name(emt_att%npm) )
1466                   CALL get_variable ( id_emis, "pm_name", string_values, emt_att%npm )
1467                   emt_att%pm_name = string_values
1468                   IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)     
1469
1470!
1471!-- PM composition (PM1, PM2.5 and PM10)
1472
1473                   len_dims = 3  ! PM1, PM2.5, PM10
1474                   ALLOCATE(emt_att%pm_comp(emt_att%ncat,emt_att%npm,len_dims))
1475                   CALL get_variable ( id_emis, "composition_pm", emt_att%pm_comp,       &
1476                                       1, emt_att%ncat, 1, emt_att%npm, 1, len_dims )
1477
1478                ENDIF  ! PM
1479
1480!
1481!-- NOX (NO and NO2)
1482
1483                IF  ( TRIM(emt_att%species_name(ispec)) == "NOX" .OR.                  &
1484                      TRIM(emt_att%species_name(ispec)) == "nox" )  THEN
1485
1486                   ALLOCATE ( emt_att%nox_comp(emt_att%ncat,emt_att%nnox) )
1487                   CALL get_variable ( id_emis, "composition_nox", emt_att%nox_comp,     &
1488                                       1, emt_att%ncat, 1, emt_att%nnox )
1489
1490                ENDIF  ! NOX
1491
1492!
1493!-- SOX (SO2 and SO4)
1494
1495                IF  ( TRIM(emt_att%species_name(ispec)) == "SOX" .OR.                  &
1496                      TRIM(emt_att%species_name(ispec)) == "sox" )  THEN
1497
1498                   ALLOCATE ( emt_att%sox_comp(emt_att%ncat,emt_att%nsox) )
1499                   CALL get_variable ( id_emis, "composition_sox", emt_att%sox_comp,     &
1500                                       1, emt_att%ncat, 1, emt_att%nsox )
1501
1502                ENDIF  ! SOX
1503
1504             ENDDO  ! do ispec
1505
1506!
1507!-- EMISSION TIME SCALING FACTORS (hourly and MDH data)
1508 
1509!     
1510!-- HOUR   
1511             IF  ( TRIM(time_fac_type) == "HOUR" .OR.                        &
1512                   TRIM(time_fac_type) == "hour" )  THEN
1513
1514                CALL netcdf_data_input_get_dimension_length (                  &
1515                                       id_emis, emt_att%nhoursyear, 'nhoursyear' )
1516                ALLOCATE ( emt_att%hourly_emis_time_factor(emt_att%ncat,emt_att%nhoursyear) )
1517                CALL get_variable ( id_emis, "emission_time_factors",          &
1518                                    emt_att%hourly_emis_time_factor,           &
1519                                    1, emt_att%ncat, 1, emt_att%nhoursyear )
1520
1521!
1522!-- MDH
1523
1524             ELSE IF  ( TRIM(time_fac_type)  ==  "MDH" .OR.                  &
1525                        TRIM(time_fac_type)  ==  "mdh" )  THEN
1526
1527                CALL netcdf_data_input_get_dimension_length (                  &
1528                                       id_emis, emt_att%nmonthdayhour, 'nmonthdayhour' )
1529                ALLOCATE ( emt_att%mdh_emis_time_factor(emt_att%ncat,emt_att%nmonthdayhour) )
1530                CALL get_variable ( id_emis, "emission_time_factors",          &
1531                                    emt_att%mdh_emis_time_factor,              &
1532                                    1, emt_att%ncat, 1, emt_att%nmonthdayhour )
1533
1534!
1535!-- ERROR (time factor undefined)
1536
1537             ELSE
1538
1539                message_string = 'We are in the DEFAULT chemistry emissions mode: '  //  &
1540                                 '     !no time-factor type specified!'              //  &
1541                                 'Please specify the value of time_fac_type:'        //  &
1542                                 '         either "MDH" or "HOUR"'                 
1543                CALL message( 'netcdf_data_input_chemistry_data', 'CM0200', 2, 2, 0, 6, 0 ) 
1544 
1545
1546             ENDIF  ! time_fac_type
1547
1548!
1549!-- read in default (LOD1) emissions from chemisty netCDF file per species
1550
1551!
1552!-- NOTE - at the moment the data is read in per species, but in the future it would
1553!--        be much more sensible to read in per species per time step to reduce
1554!--        memory consumption and, to a lesser degree, dimensionality of data exchange
1555!--        (I expect this will be necessary when the problem size is large)
1556
1557             DO ispec = 1, emt_att%n_emiss_species
1558
1559!
1560!-- allocate space for species specific emission values
1561!-- NOTE - this array is extended by 1 cell in each horizontal direction
1562!--        to compensate for an apparent linear offset.  The reason of this
1563!--        offset is not known but it has been determined to take place beyond the
1564!--        scope of this module, and has little to do with index conventions.
1565!--        That is, setting the array horizontal limit from nx0:nx1 to 1:(nx1-nx0+1)
1566!--        or nx0+1:nx1+1 did not result in correct or definite behavior
1567!--        This must be looked at at some point by the Hannover team but for now
1568!--        this workaround is deemed reasonable (ecc 20190417)
1569
1570                IF ( .NOT. ALLOCATED ( emt(ispec)%default_emission_data ) )  THEN
1571                    ALLOCATE ( emt(ispec)%default_emission_data(emt_att%ncat,nys:nyn+1,nxl:nxr+1) )
1572                ENDIF
1573!
1574!-- allocate dummy variable w/ index order identical to that shown in the netCDF header
1575
1576                ALLOCATE ( dum_var_5d(1,nys:nyn,nxl:nxr,1,emt_att%ncat) )
1577!
1578!-- get variable.  be very careful
1579!-- I am using get_variable_5d_real_dynamic (note logical argument at the end)
1580!-- 1) use Fortran index convention (i.e., 1 to N)
1581!-- 2) index order must be in reverse order from above allocation order
1582 
1583                CALL get_variable ( id_emis, "emission_values", dum_var_5d, &
1584                                    1,            ispec, nxl+1,     nys+1,     1,                    &
1585                                    emt_att%ncat, 1,     nxr-nxl+1, nyn-nys+1, emt_att%dt_emission,  &
1586                                    .FALSE. )
1587!
1588!-- assign temp array to data structure then deallocate temp array
1589!-- NOTE - indices are shifted from nx0:nx1 to nx0+1:nx1+1 to offset
1590!--        the emission data array to counter said domain offset
1591!--        (ecc 20190417)
1592
1593                DO k = 1, emt_att%ncat
1594                   DO j = nys+1, nyn+1
1595                      DO i = nxl+1, nxr+1
1596                         emt(ispec)%default_emission_data(k,j,i) = dum_var_5d(1,j-1,i-1,1,k)
1597                      ENDDO
1598                   ENDDO
1599                ENDDO
1600
1601                DEALLOCATE ( dum_var_5d )
1602
1603             ENDDO  ! ispec
1604!
1605!-- UNITS
1606
1607             CALL get_attribute(id_emis,"units",emt_att%units,.FALSE.,"emission_values")
1608
1609!
1610!-- END DEFAULT MODE
1611
1612
1613!
1614!-- START LOD 2 (PRE-PROCESSED MODE)
1615
1616          ELSE IF  ( emiss_lod == 2 )  THEN
1617
1618! for reference (ecc)
1619!          ELSE IF (TRIM(mode_emis) == "PRE-PROCESSED" .OR. TRIM(mode_emis) == "pre-processed") THEN
1620
1621!
1622!-- For LOD 2 only VOC and emission data need be read
1623
1624!------------------------------------------------------------------------------
1625!-- NOTE - CHECK ARRAY INDICES FOR READING IN NAMES AND SPECIES
1626!--        IN LOD2 (PRE-PROCESSED MODE) FOR THE VARIOUS MODE SPLITS
1627!--        AS ALL ID_EMIS CONDITIONALS HAVE BEEN REMOVED FROM GET_VAR
1628!--        FUNCTIONS.  IN THEORY THIS WOULD MEAN ALL ARRAYS SHOULD BE
1629!--        READ FROM 0 to N-1 (C CONVENTION) AS OPPOSED TO 1 to N
1630!--        (FORTRAN CONVENTION).  KEEP THIS IN MIND !!
1631!--        (ecc 20190424)
1632!------------------------------------------------------------------------------
1633
1634             DO ispec = 1, emt_att%n_emiss_species
1635
1636!
1637!-- VOC DATA (name and composition)
1638
1639                IF  ( TRIM(emt_att%species_name(ispec)) == "VOC" .OR.                  &
1640                      TRIM(emt_att%species_name(ispec)) == "voc" )  THEN
1641
1642!
1643!-- VOC name
1644                   CALL netcdf_data_input_get_dimension_length (                         &
1645                                          id_emis, emt_att%nvoc, 'nvoc' )
1646                   ALLOCATE ( emt_att%voc_name(emt_att%nvoc) )
1647                   CALL get_variable ( id_emis, "emission_voc_name",                     &
1648                                       string_values, emt_att%nvoc)
1649                   emt_att%voc_name = string_values
1650                   IF  ( ALLOCATED(string_values) )  DEALLOCATE (string_values)
1651
1652!
1653!-- VOC composition
1654 
1655                   ALLOCATE ( emt_att%voc_comp(emt_att%ncat,emt_att%nvoc) )
1656                   CALL get_variable ( id_emis, "composition_voc", emt_att%voc_comp,     &
1657                                       1, emt_att%ncat, 1, emt_att%nvoc )
1658                ENDIF  ! VOC
1659 
1660             ENDDO  ! ispec
1661
1662!
1663!-- EMISSION DATA
1664
1665             CALL netcdf_data_input_get_dimension_length (                               &
1666                                    id_emis, emt_att%dt_emission, 'time' )   
1667 
1668!
1669!-- read in pre-processed (LOD2) emissions from chemisty netCDF file per species
1670
1671!
1672!-- NOTE - at the moment the data is read in per species, but in the future it would
1673!--        be much more sensible to read in per species per time step to reduce
1674!--        memory consumption and, to a lesser degree, dimensionality of data exchange
1675!--        (I expect this will be necessary when the problem size is large)
1676
1677             DO ispec = 1, emt_att%n_emiss_species
1678
1679!
1680!-- allocate space for species specific emission values
1681!-- NOTE - this array is extended by 1 cell in each horizontal direction
1682!--        to compensate for an apparent linear offset.  The reason of this
1683!--        offset is not known but it has been determined to take place beyond the
1684!--        scope of this module, and has little to do with index conventions.
1685!--        That is, setting the array horizontal limit from nx0:nx1 to 1:(nx1-nx0+1)
1686!--        or nx0+1:nx1+1 did not result in correct or definite behavior
1687!--        This must be looked at at some point by the Hannover team but for now
1688!--        this workaround is deemed reasonable (ecc 20190417)
1689
1690                IF ( .NOT. ALLOCATED( emt(ispec)%preproc_emission_data ) )  THEN
1691                   ALLOCATE( emt(ispec)%preproc_emission_data(                           &
1692                             emt_att%dt_emission, 1, nys:nyn+1, nxl:nxr+1) )
1693                ENDIF
1694!
1695!-- allocate dummy variable w/ index order identical to that shown in the netCDF header
1696
1697                ALLOCATE ( dum_var_5d(emt_att%dt_emission,1,nys:nyn,nxl:nxr,1) )
1698!
1699!-- get variable.  be very careful
1700!-- I am using get_variable_5d_real_dynamic (note logical argument at the end)
1701!-- 1) use Fortran index convention (i.e., 1 to N)
1702!-- 2) index order must be in reverse order from above allocation order
1703
1704                CALL get_variable ( id_emis, "emission_values", dum_var_5d, &
1705                                    ispec, nxl+1,     nys+1,     1, 1,                   &
1706                                    1,     nxr-nxl+1, nyn-nys+1, 1, emt_att%dt_emission, &
1707                                    .FALSE. )
1708!
1709!-- assign temp array to data structure then deallocate temp array
1710!-- NOTE - indices are shifted from nx0:nx1 to nx0+1:nx1+1 to offset
1711!--        the emission data array to counter said unkonwn offset
1712!--        (ecc 20190417)
1713
1714                DO k = 1, emt_att%dt_emission
1715                   DO j = nys+1, nyn+1
1716                      DO i = nxl+1, nxr+1
1717                         emt(ispec)%preproc_emission_data(k,1,j,i) = dum_var_5d(k,1,j-1,i-1,1)
1718                      ENDDO
1719                   ENDDO
1720                ENDDO
1721
1722                DEALLOCATE ( dum_var_5d )
1723
1724             ENDDO  ! ispec
1725!
1726!-- UNITS
1727
1728             CALL get_attribute ( id_emis, "units", emt_att%units, .FALSE. , "emission_values" )
1729       
1730          ENDIF  ! LOD1 & LOD2 (default and pre-processed mode)
1731
1732          CALL close_input_file (id_emis)
1733
1734#endif
1735
1736       ENDIF ! LOD0 (parameterized mode)
1737
1738    END SUBROUTINE netcdf_data_input_chemistry_data
1739
1740
1741!------------------------------------------------------------------------------!
1742! Description:
1743! ------------
1744!> Reads surface classification data, such as vegetation and soil type, etc. .
1745!------------------------------------------------------------------------------!
1746    SUBROUTINE netcdf_data_input_surface_data
1747
1748       USE control_parameters,                                                 &
1749           ONLY:  land_surface, plant_canopy, urban_surface
1750
1751       USE indices,                                                            &
1752           ONLY:  nbgp, nxl, nxr, nyn, nys
1753
1754
1755       IMPLICIT NONE
1756
1757       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names in static input file
1758
1759       INTEGER(iwp) ::  id_surf   !< NetCDF id of input file
1760       INTEGER(iwp) ::  k         !< running index along z-direction
1761       INTEGER(iwp) ::  k2        !< running index
1762       INTEGER(iwp) ::  num_vars  !< number of variables in input file
1763       INTEGER(iwp) ::  nz_soil   !< number of soil layers in file
1764
1765!
1766!--    If not static input file is available, skip this routine
1767       IF ( .NOT. input_pids_static )  RETURN
1768!
1769!--    Measure CPU time
1770       CALL cpu_log( log_point_s(82), 'NetCDF input', 'start' )
1771!
1772!--    Read plant canopy variables.
1773       IF ( plant_canopy )  THEN
1774#if defined ( __netcdf )
1775!
1776!--       Open file in read-only mode
1777          CALL open_read_file( TRIM( input_file_static ) //                    &
1778                               TRIM( coupling_char ) , id_surf )
1779!
1780!--       At first, inquire all variable names.
1781!--       This will be used to check whether an optional input variable
1782!--       exist or not.
1783          CALL inquire_num_variables( id_surf, num_vars )
1784
1785          ALLOCATE( var_names(1:num_vars) )
1786          CALL inquire_variable_names( id_surf, var_names )
1787
1788!
1789!--       Read leaf area density - resolved vegetation
1790          IF ( check_existence( var_names, 'lad' ) )  THEN
1791             leaf_area_density_f%from_file = .TRUE.
1792             CALL get_attribute( id_surf, char_fill,                           &
1793                                 leaf_area_density_f%fill,                     &
1794                                 .FALSE., 'lad' )
1795!
1796!--          Inquire number of vertical vegetation layer
1797             CALL netcdf_data_input_get_dimension_length( id_surf,             &
1798                                                 leaf_area_density_f%nz,       &
1799                                                 'zlad' )
1800!
1801!--          Allocate variable for leaf-area density
1802             ALLOCATE( leaf_area_density_f%var( 0:leaf_area_density_f%nz-1,    &
1803                                                nys:nyn,nxl:nxr) )
1804
1805             CALL get_variable( id_surf, 'lad', leaf_area_density_f%var,       &
1806                                nxl, nxr, nys, nyn,                            &
1807                                0, leaf_area_density_f%nz-1 )
1808
1809          ELSE
1810             leaf_area_density_f%from_file = .FALSE.
1811          ENDIF
1812
1813!
1814!--       Read basal area density - resolved vegetation
1815          IF ( check_existence( var_names, 'bad' ) )  THEN
1816             basal_area_density_f%from_file = .TRUE.
1817             CALL get_attribute( id_surf, char_fill,                           &
1818                                 basal_area_density_f%fill,                    &
1819                                 .FALSE., 'bad' )
1820!
1821!--          Inquire number of vertical vegetation layer
1822             CALL netcdf_data_input_get_dimension_length( id_surf,             &
1823                                                 basal_area_density_f%nz,      &
1824                                                 'zlad' )
1825!
1826!--          Allocate variable
1827             ALLOCATE( basal_area_density_f%var(0:basal_area_density_f%nz-1,   &
1828                                                nys:nyn,nxl:nxr) )
1829
1830             CALL get_variable( id_surf, 'bad', basal_area_density_f%var,      &
1831                                nxl, nxr, nys, nyn,                            &
1832                                0,  basal_area_density_f%nz-1 )
1833          ELSE
1834             basal_area_density_f%from_file = .FALSE.
1835          ENDIF
1836
1837!
1838!--       Read root area density - resolved vegetation
1839          IF ( check_existence( var_names, 'root_area_dens_r' ) )  THEN
1840             root_area_density_lad_f%from_file = .TRUE.
1841             CALL get_attribute( id_surf, char_fill,                           &
1842                                 root_area_density_lad_f%fill,                 &
1843                                 .FALSE., 'root_area_dens_r' )
1844!
1845!--          Inquire number of vertical soil layers
1846             CALL netcdf_data_input_get_dimension_length( id_surf,             &
1847                                                   root_area_density_lad_f%nz, &
1848                                                  'zsoil' )
1849!
1850!--          Allocate variable
1851             ALLOCATE( root_area_density_lad_f%var                             &
1852                                         (0:root_area_density_lad_f%nz-1,      &
1853                                          nys:nyn,nxl:nxr) )
1854
1855             CALL get_variable( id_surf, 'root_area_dens_r',                   &
1856                                root_area_density_lad_f%var,                   &
1857                                nxl, nxr, nys, nyn,                            &
1858                                0,  root_area_density_lad_f%nz-1 )
1859          ELSE
1860             root_area_density_lad_f%from_file = .FALSE.
1861          ENDIF
1862!
1863!--       Finally, close input file
1864          CALL close_input_file( id_surf )
1865#endif
1866       ENDIF
1867!
1868!--    Deallocate variable list. Will be re-allocated in case further
1869!--    variables are read from file.
1870       IF ( ALLOCATED( var_names ) )  DEALLOCATE( var_names )
1871!
1872!--    Skip the following if no land-surface or urban-surface module are
1873!--    applied. This case, no one of the following variables is used anyway.
1874       IF (  .NOT. land_surface  .AND.  .NOT. urban_surface )  RETURN
1875
1876#if defined ( __netcdf )
1877!
1878!--    Open file in read-only mode
1879       CALL open_read_file( TRIM( input_file_static ) //                       &
1880                            TRIM( coupling_char ) , id_surf )
1881!
1882!--    Inquire all variable names.
1883!--    This will be used to check whether an optional input variable exist
1884!--    or not.
1885       CALL inquire_num_variables( id_surf, num_vars )
1886
1887       ALLOCATE( var_names(1:num_vars) )
1888       CALL inquire_variable_names( id_surf, var_names )
1889!
1890!--    Read vegetation type and required attributes
1891       IF ( check_existence( var_names, 'vegetation_type' ) )  THEN
1892          vegetation_type_f%from_file = .TRUE.
1893          CALL get_attribute( id_surf, char_fill,                              &
1894                              vegetation_type_f%fill,                          &
1895                              .FALSE., 'vegetation_type' )
1896
1897          ALLOCATE ( vegetation_type_f%var(nys:nyn,nxl:nxr)  )
1898
1899          CALL get_variable( id_surf, 'vegetation_type',                       &
1900                             vegetation_type_f%var, nxl, nxr, nys, nyn )
1901       ELSE
1902          vegetation_type_f%from_file = .FALSE.
1903       ENDIF
1904
1905!
1906!--    Read soil type and required attributes
1907       IF ( check_existence( var_names, 'soil_type' ) )  THEN
1908             soil_type_f%from_file = .TRUE.
1909!
1910!--       Note, lod is currently not on file; skip for the moment
1911!           CALL get_attribute( id_surf, char_lod,                       &
1912!                                      soil_type_f%lod,                  &
1913!                                      .FALSE., 'soil_type' )
1914          CALL get_attribute( id_surf, char_fill,                              &
1915                              soil_type_f%fill,                                &
1916                              .FALSE., 'soil_type' )
1917
1918          IF ( soil_type_f%lod == 1 )  THEN
1919
1920             ALLOCATE ( soil_type_f%var_2d(nys:nyn,nxl:nxr)  )
1921
1922             CALL get_variable( id_surf, 'soil_type', soil_type_f%var_2d,      &
1923                                nxl, nxr, nys, nyn )
1924
1925          ELSEIF ( soil_type_f%lod == 2 )  THEN
1926!
1927!--          Obtain number of soil layers from file.
1928             CALL netcdf_data_input_get_dimension_length( id_surf, nz_soil,    &
1929                                                          'zsoil' )
1930
1931             ALLOCATE ( soil_type_f%var_3d(0:nz_soil,nys:nyn,nxl:nxr) )
1932
1933             CALL get_variable( id_surf, 'soil_type', soil_type_f%var_3d,      &
1934                                nxl, nxr, nys, nyn, 0, nz_soil )
1935 
1936          ENDIF
1937       ELSE
1938          soil_type_f%from_file = .FALSE.
1939       ENDIF
1940
1941!
1942!--    Read pavement type and required attributes
1943       IF ( check_existence( var_names, 'pavement_type' ) )  THEN
1944          pavement_type_f%from_file = .TRUE.
1945          CALL get_attribute( id_surf, char_fill,                              &
1946                              pavement_type_f%fill, .FALSE.,                   &
1947                              'pavement_type' )
1948
1949          ALLOCATE ( pavement_type_f%var(nys:nyn,nxl:nxr)  )
1950
1951          CALL get_variable( id_surf, 'pavement_type', pavement_type_f%var,    &
1952                             nxl, nxr, nys, nyn )
1953       ELSE
1954          pavement_type_f%from_file = .FALSE.
1955       ENDIF
1956
1957!
1958!--    Read water type and required attributes
1959       IF ( check_existence( var_names, 'water_type' ) )  THEN
1960          water_type_f%from_file = .TRUE.
1961          CALL get_attribute( id_surf, char_fill, water_type_f%fill,           &
1962                              .FALSE., 'water_type' )
1963
1964          ALLOCATE ( water_type_f%var(nys:nyn,nxl:nxr)  )
1965
1966          CALL get_variable( id_surf, 'water_type', water_type_f%var,          &
1967                             nxl, nxr, nys, nyn )
1968
1969       ELSE
1970          water_type_f%from_file = .FALSE.
1971       ENDIF
1972!
1973!--    Read relative surface fractions of vegetation, pavement and water.
1974       IF ( check_existence( var_names, 'surface_fraction' ) )  THEN
1975          surface_fraction_f%from_file = .TRUE.
1976          CALL get_attribute( id_surf, char_fill,                              &
1977                              surface_fraction_f%fill,                         &
1978                              .FALSE., 'surface_fraction' )
1979!
1980!--       Inquire number of surface fractions
1981          CALL netcdf_data_input_get_dimension_length( id_surf,                &
1982                                                       surface_fraction_f%nf,  &
1983                                                       'nsurface_fraction' )
1984!
1985!--       Allocate dimension array and input array for surface fractions
1986          ALLOCATE( surface_fraction_f%nfracs(0:surface_fraction_f%nf-1) )
1987          ALLOCATE( surface_fraction_f%frac(0:surface_fraction_f%nf-1,         &
1988                                            nys:nyn,nxl:nxr) )
1989!
1990!--       Get dimension of surface fractions
1991          CALL get_variable( id_surf, 'nsurface_fraction',                     &
1992                             surface_fraction_f%nfracs )
1993!
1994!--       Read surface fractions
1995          CALL get_variable( id_surf, 'surface_fraction',                      &
1996                             surface_fraction_f%frac, nxl, nxr, nys, nyn,      &
1997                             0, surface_fraction_f%nf-1 )
1998       ELSE
1999          surface_fraction_f%from_file = .FALSE.
2000       ENDIF
2001!
2002!--    Read building parameters and related information
2003       IF ( check_existence( var_names, 'building_pars' ) )  THEN
2004          building_pars_f%from_file = .TRUE.
2005          CALL get_attribute( id_surf, char_fill,                              &
2006                              building_pars_f%fill,                            &
2007                              .FALSE., 'building_pars' )
2008!
2009!--       Inquire number of building parameters
2010          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2011                                                       building_pars_f%np,     &
2012                                                       'nbuilding_pars' )
2013!
2014!--       Allocate dimension array and input array for building parameters
2015          ALLOCATE( building_pars_f%pars(0:building_pars_f%np-1) )
2016          ALLOCATE( building_pars_f%pars_xy(0:building_pars_f%np-1,            &
2017                                            nys:nyn,nxl:nxr) )
2018!
2019!--       Get dimension of building parameters
2020          CALL get_variable( id_surf, 'nbuilding_pars',                        &
2021                             building_pars_f%pars )
2022!
2023!--       Read building_pars
2024          CALL get_variable( id_surf, 'building_pars',                         &
2025                             building_pars_f%pars_xy, nxl, nxr, nys, nyn,      &
2026                             0, building_pars_f%np-1 )
2027       ELSE
2028          building_pars_f%from_file = .FALSE.
2029       ENDIF
2030
2031!
2032!--    Read albedo type and required attributes
2033       IF ( check_existence( var_names, 'albedo_type' ) )  THEN
2034          albedo_type_f%from_file = .TRUE.
2035          CALL get_attribute( id_surf, char_fill, albedo_type_f%fill,          &
2036                              .FALSE.,  'albedo_type' )
2037
2038          ALLOCATE ( albedo_type_f%var(nys:nyn,nxl:nxr)  )
2039         
2040          CALL get_variable( id_surf, 'albedo_type', albedo_type_f%var,        &
2041                             nxl, nxr, nys, nyn )
2042       ELSE
2043          albedo_type_f%from_file = .FALSE.
2044       ENDIF
2045!
2046!--    Read albedo parameters and related information
2047       IF ( check_existence( var_names, 'albedo_pars' ) )  THEN
2048          albedo_pars_f%from_file = .TRUE.
2049          CALL get_attribute( id_surf, char_fill, albedo_pars_f%fill,          &
2050                              .FALSE., 'albedo_pars' )
2051!
2052!--       Inquire number of albedo parameters
2053          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2054                                                       albedo_pars_f%np,       &
2055                                                       'nalbedo_pars' )
2056!
2057!--       Allocate dimension array and input array for albedo parameters
2058          ALLOCATE( albedo_pars_f%pars(0:albedo_pars_f%np-1) )
2059          ALLOCATE( albedo_pars_f%pars_xy(0:albedo_pars_f%np-1,                &
2060                                          nys:nyn,nxl:nxr) )
2061!
2062!--       Get dimension of albedo parameters
2063          CALL get_variable( id_surf, 'nalbedo_pars', albedo_pars_f%pars )
2064
2065          CALL get_variable( id_surf, 'albedo_pars', albedo_pars_f%pars_xy,    &
2066                             nxl, nxr, nys, nyn,                               &
2067                             0, albedo_pars_f%np-1 )
2068       ELSE
2069          albedo_pars_f%from_file = .FALSE.
2070       ENDIF
2071
2072!
2073!--    Read pavement parameters and related information
2074       IF ( check_existence( var_names, 'pavement_pars' ) )  THEN
2075          pavement_pars_f%from_file = .TRUE.
2076          CALL get_attribute( id_surf, char_fill,                              &
2077                              pavement_pars_f%fill,                            &
2078                              .FALSE., 'pavement_pars' )
2079!
2080!--       Inquire number of pavement parameters
2081          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2082                                                       pavement_pars_f%np,     &
2083                                                       'npavement_pars' )
2084!
2085!--       Allocate dimension array and input array for pavement parameters
2086          ALLOCATE( pavement_pars_f%pars(0:pavement_pars_f%np-1) )
2087          ALLOCATE( pavement_pars_f%pars_xy(0:pavement_pars_f%np-1,            &
2088                                            nys:nyn,nxl:nxr) )
2089!
2090!--       Get dimension of pavement parameters
2091          CALL get_variable( id_surf, 'npavement_pars', pavement_pars_f%pars )
2092
2093          CALL get_variable( id_surf, 'pavement_pars', pavement_pars_f%pars_xy,&
2094                             nxl, nxr, nys, nyn,                               &
2095                             0, pavement_pars_f%np-1 )
2096       ELSE
2097          pavement_pars_f%from_file = .FALSE.
2098       ENDIF
2099
2100!
2101!--    Read pavement subsurface parameters and related information
2102       IF ( check_existence( var_names, 'pavement_subsurface_pars' ) )         &
2103       THEN
2104          pavement_subsurface_pars_f%from_file = .TRUE.
2105          CALL get_attribute( id_surf, char_fill,                              &
2106                              pavement_subsurface_pars_f%fill,                 &
2107                              .FALSE., 'pavement_subsurface_pars' )
2108!
2109!--       Inquire number of parameters
2110          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2111                                                pavement_subsurface_pars_f%np, &
2112                                               'npavement_subsurface_pars' )
2113!
2114!--       Inquire number of soil layers
2115          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2116                                                pavement_subsurface_pars_f%nz, &
2117                                                'zsoil' )
2118!
2119!--       Allocate dimension array and input array for pavement parameters
2120          ALLOCATE( pavement_subsurface_pars_f%pars                            &
2121                            (0:pavement_subsurface_pars_f%np-1) )
2122          ALLOCATE( pavement_subsurface_pars_f%pars_xyz                        &
2123                            (0:pavement_subsurface_pars_f%np-1,                &
2124                             0:pavement_subsurface_pars_f%nz-1,                &
2125                             nys:nyn,nxl:nxr) )
2126!
2127!--       Get dimension of pavement parameters
2128          CALL get_variable( id_surf, 'npavement_subsurface_pars',             &
2129                             pavement_subsurface_pars_f%pars )
2130
2131          CALL get_variable( id_surf, 'pavement_subsurface_pars',              &
2132                             pavement_subsurface_pars_f%pars_xyz,              &
2133                             nxl, nxr, nys, nyn,                               &
2134                             0, pavement_subsurface_pars_f%nz-1,               &
2135                             0, pavement_subsurface_pars_f%np-1 )
2136       ELSE
2137          pavement_subsurface_pars_f%from_file = .FALSE.
2138       ENDIF
2139
2140
2141!
2142!--    Read vegetation parameters and related information
2143       IF ( check_existence( var_names, 'vegetation_pars' ) )  THEN
2144          vegetation_pars_f%from_file = .TRUE.
2145          CALL get_attribute( id_surf, char_fill,                              &
2146                              vegetation_pars_f%fill,                          &
2147                              .FALSE.,  'vegetation_pars' )
2148!
2149!--       Inquire number of vegetation parameters
2150          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2151                                                       vegetation_pars_f%np,   &
2152                                                       'nvegetation_pars' )
2153!
2154!--       Allocate dimension array and input array for surface fractions
2155          ALLOCATE( vegetation_pars_f%pars(0:vegetation_pars_f%np-1) )
2156          ALLOCATE( vegetation_pars_f%pars_xy(0:vegetation_pars_f%np-1,        &
2157                                              nys:nyn,nxl:nxr) )
2158!
2159!--       Get dimension of the parameters
2160          CALL get_variable( id_surf, 'nvegetation_pars',                      &
2161                             vegetation_pars_f%pars )
2162
2163          CALL get_variable( id_surf, 'vegetation_pars',                       &
2164                             vegetation_pars_f%pars_xy, nxl, nxr, nys, nyn,    &
2165                             0, vegetation_pars_f%np-1 )
2166       ELSE
2167          vegetation_pars_f%from_file = .FALSE.
2168       ENDIF
2169
2170!
2171!--    Read root parameters/distribution and related information
2172       IF ( check_existence( var_names, 'soil_pars' ) )  THEN
2173          soil_pars_f%from_file = .TRUE.
2174          CALL get_attribute( id_surf, char_fill,                              &
2175                              soil_pars_f%fill,                                &
2176                              .FALSE., 'soil_pars' )
2177
2178          CALL get_attribute( id_surf, char_lod,                               &
2179                              soil_pars_f%lod,                                 &
2180                              .FALSE., 'soil_pars' )
2181
2182!
2183!--       Inquire number of soil parameters
2184          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2185                                                       soil_pars_f%np,         &
2186                                                       'nsoil_pars' )
2187!
2188!--       Read parameters array
2189          ALLOCATE( soil_pars_f%pars(0:soil_pars_f%np-1) )
2190          CALL get_variable( id_surf, 'nsoil_pars', soil_pars_f%pars )
2191
2192!
2193!--       In case of level of detail 2, also inquire number of vertical
2194!--       soil layers, allocate memory and read the respective dimension
2195          IF ( soil_pars_f%lod == 2 )  THEN
2196             CALL netcdf_data_input_get_dimension_length( id_surf,             &
2197                                                          soil_pars_f%nz,      &
2198                                                          'zsoil' )
2199
2200             ALLOCATE( soil_pars_f%layers(0:soil_pars_f%nz-1) )
2201             CALL get_variable( id_surf, 'zsoil', soil_pars_f%layers )
2202
2203          ENDIF
2204
2205!
2206!--       Read soil parameters, depending on level of detail
2207          IF ( soil_pars_f%lod == 1 )  THEN
2208             ALLOCATE( soil_pars_f%pars_xy(0:soil_pars_f%np-1,                 &
2209                                           nys:nyn,nxl:nxr) )
2210                 
2211             CALL get_variable( id_surf, 'soil_pars', soil_pars_f%pars_xy,     &
2212                                nxl, nxr, nys, nyn, 0, soil_pars_f%np-1 )
2213
2214          ELSEIF ( soil_pars_f%lod == 2 )  THEN
2215             ALLOCATE( soil_pars_f%pars_xyz(0:soil_pars_f%np-1,                &
2216                                            0:soil_pars_f%nz-1,                &
2217                                            nys:nyn,nxl:nxr) )
2218             CALL get_variable( id_surf, 'soil_pars',                          &
2219                                soil_pars_f%pars_xyz,                          &
2220                                nxl, nxr, nys, nyn, 0, soil_pars_f%nz-1,       &
2221                                0, soil_pars_f%np-1 )
2222
2223          ENDIF
2224       ELSE
2225          soil_pars_f%from_file = .FALSE.
2226       ENDIF
2227
2228!
2229!--    Read water parameters and related information
2230       IF ( check_existence( var_names, 'water_pars' ) )  THEN
2231          water_pars_f%from_file = .TRUE.
2232          CALL get_attribute( id_surf, char_fill,                              &
2233                              water_pars_f%fill,                               &
2234                              .FALSE., 'water_pars' )
2235!
2236!--       Inquire number of water parameters
2237          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2238                                                       water_pars_f%np,        &
2239                                                       'nwater_pars' )
2240!
2241!--       Allocate dimension array and input array for water parameters
2242          ALLOCATE( water_pars_f%pars(0:water_pars_f%np-1) )
2243          ALLOCATE( water_pars_f%pars_xy(0:water_pars_f%np-1,                  &
2244                                         nys:nyn,nxl:nxr) )
2245!
2246!--       Get dimension of water parameters
2247          CALL get_variable( id_surf, 'nwater_pars', water_pars_f%pars )
2248
2249          CALL get_variable( id_surf, 'water_pars', water_pars_f%pars_xy,      &
2250                             nxl, nxr, nys, nyn, 0, water_pars_f%np-1 )
2251       ELSE
2252          water_pars_f%from_file = .FALSE.
2253       ENDIF
2254!
2255!--    Read root area density - parametrized vegetation
2256       IF ( check_existence( var_names, 'root_area_dens_s' ) )  THEN
2257          root_area_density_lsm_f%from_file = .TRUE.
2258          CALL get_attribute( id_surf, char_fill,                              &
2259                              root_area_density_lsm_f%fill,                    &
2260                              .FALSE., 'root_area_dens_s' )
2261!
2262!--       Obtain number of soil layers from file and allocate variable
2263          CALL netcdf_data_input_get_dimension_length( id_surf,                &
2264                                                   root_area_density_lsm_f%nz, &
2265                                                   'zsoil' )
2266          ALLOCATE( root_area_density_lsm_f%var                                &
2267                                        (0:root_area_density_lsm_f%nz-1,       &
2268                                         nys:nyn,nxl:nxr) )
2269
2270!
2271!--       Read root-area density
2272          CALL get_variable( id_surf, 'root_area_dens_s',                      &
2273                             root_area_density_lsm_f%var,                      &
2274                             nxl, nxr, nys, nyn,                               &
2275                             0, root_area_density_lsm_f%nz-1 )
2276
2277       ELSE
2278          root_area_density_lsm_f%from_file = .FALSE.
2279       ENDIF
2280!
2281!--    Read street type and street crossing
2282       IF ( check_existence( var_names, 'street_type' ) )  THEN
2283          street_type_f%from_file = .TRUE.
2284          CALL get_attribute( id_surf, char_fill,                              &
2285                              street_type_f%fill, .FALSE.,                     &
2286                              'street_type' )
2287
2288          ALLOCATE ( street_type_f%var(nys:nyn,nxl:nxr)  )
2289         
2290          CALL get_variable( id_surf, 'street_type', street_type_f%var,        &
2291                             nxl, nxr, nys, nyn )
2292       ELSE
2293          street_type_f%from_file = .FALSE.
2294       ENDIF
2295
2296       IF ( check_existence( var_names, 'street_crossing' ) )  THEN
2297          street_crossing_f%from_file = .TRUE.
2298          CALL get_attribute( id_surf, char_fill,                              &
2299                              street_crossing_f%fill, .FALSE.,                 &
2300                              'street_crossing' )
2301
2302          ALLOCATE ( street_crossing_f%var(nys:nyn,nxl:nxr)  )
2303
2304          CALL get_variable( id_surf, 'street_crossing',                       &
2305                             street_crossing_f%var, nxl, nxr, nys, nyn )
2306
2307       ELSE
2308          street_crossing_f%from_file = .FALSE.
2309       ENDIF
2310!
2311!--    Still missing: root_resolved and building_surface_pars.
2312!--    Will be implemented as soon as they are available.
2313
2314!
2315!--    Finally, close input file
2316       CALL close_input_file( id_surf )
2317#endif
2318!
2319!--    End of CPU measurement
2320       CALL cpu_log( log_point_s(82), 'NetCDF input', 'stop' )
2321!
2322!--    Exchange ghost points for surface variables. Therefore, resize
2323!--    variables.
2324       IF ( albedo_type_f%from_file )  THEN
2325          CALL resize_array_2d_int8( albedo_type_f%var, nys, nyn, nxl, nxr )
2326          CALL exchange_horiz_2d_byte( albedo_type_f%var, nys, nyn, nxl, nxr,  &
2327                                       nbgp )
2328       ENDIF
2329       IF ( pavement_type_f%from_file )  THEN
2330          CALL resize_array_2d_int8( pavement_type_f%var, nys, nyn, nxl, nxr )
2331          CALL exchange_horiz_2d_byte( pavement_type_f%var, nys, nyn, nxl, nxr,&
2332                                       nbgp )
2333       ENDIF
2334       IF ( soil_type_f%from_file  .AND.  ALLOCATED( soil_type_f%var_2d ) )  THEN
2335          CALL resize_array_2d_int8( soil_type_f%var_2d, nys, nyn, nxl, nxr )
2336          CALL exchange_horiz_2d_byte( soil_type_f%var_2d, nys, nyn, nxl, nxr, &
2337                                       nbgp )
2338       ENDIF
2339       IF ( vegetation_type_f%from_file )  THEN
2340          CALL resize_array_2d_int8( vegetation_type_f%var, nys, nyn, nxl, nxr )
2341          CALL exchange_horiz_2d_byte( vegetation_type_f%var, nys, nyn, nxl,   &
2342                                       nxr, nbgp )
2343       ENDIF
2344       IF ( water_type_f%from_file )  THEN
2345          CALL resize_array_2d_int8( water_type_f%var, nys, nyn, nxl, nxr )
2346          CALL exchange_horiz_2d_byte( water_type_f%var, nys, nyn, nxl, nxr,   &
2347                                       nbgp )
2348       ENDIF
2349!
2350!--    Exchange ghost points for 3/4-D variables. For the sake of simplicity,
2351!--    loop further dimensions to use 2D exchange routines. Unfortunately this
2352!--    is necessary, else new MPI-data types need to be introduced just for
2353!--    2 variables.
2354       IF ( soil_type_f%from_file  .AND.  ALLOCATED( soil_type_f%var_3d ) )    &
2355       THEN
2356          CALL resize_array_3d_int8( soil_type_f%var_3d, 0, nz_soil,           &
2357                                     nys, nyn, nxl, nxr )
2358          DO  k = 0, nz_soil
2359             CALL exchange_horiz_2d_int(                                       & 
2360                        soil_type_f%var_3d(k,:,:), nys, nyn, nxl, nxr, nbgp )
2361          ENDDO
2362       ENDIF
2363
2364       IF ( surface_fraction_f%from_file )  THEN
2365          CALL resize_array_3d_real( surface_fraction_f%frac,                  &
2366                                     0, surface_fraction_f%nf-1,               &
2367                                     nys, nyn, nxl, nxr )
2368          DO  k = 0, surface_fraction_f%nf-1
2369             CALL exchange_horiz_2d( surface_fraction_f%frac(k,:,:), nbgp )
2370          ENDDO
2371       ENDIF
2372
2373       IF ( building_pars_f%from_file )  THEN         
2374          CALL resize_array_3d_real( building_pars_f%pars_xy,                  &
2375                                     0, building_pars_f%np-1,                  &
2376                                     nys, nyn, nxl, nxr )
2377          DO  k = 0, building_pars_f%np-1
2378             CALL exchange_horiz_2d( building_pars_f%pars_xy(k,:,:), nbgp )
2379          ENDDO
2380       ENDIF
2381
2382       IF ( albedo_pars_f%from_file )  THEN         
2383          CALL resize_array_3d_real( albedo_pars_f%pars_xy,                    &
2384                                     0, albedo_pars_f%np-1,                    &
2385                                     nys, nyn, nxl, nxr )
2386          DO  k = 0, albedo_pars_f%np-1
2387             CALL exchange_horiz_2d( albedo_pars_f%pars_xy(k,:,:), nbgp )
2388          ENDDO
2389       ENDIF
2390
2391       IF ( pavement_pars_f%from_file )  THEN         
2392          CALL resize_array_3d_real( pavement_pars_f%pars_xy,                  &
2393                                     0, pavement_pars_f%np-1,                  &
2394                                     nys, nyn, nxl, nxr )
2395          DO  k = 0, pavement_pars_f%np-1
2396             CALL exchange_horiz_2d( pavement_pars_f%pars_xy(k,:,:), nbgp )
2397          ENDDO
2398       ENDIF
2399
2400       IF ( vegetation_pars_f%from_file )  THEN
2401          CALL resize_array_3d_real( vegetation_pars_f%pars_xy,                &
2402                                     0, vegetation_pars_f%np-1,                &
2403                                     nys, nyn, nxl, nxr )
2404          DO  k = 0, vegetation_pars_f%np-1
2405             CALL exchange_horiz_2d( vegetation_pars_f%pars_xy(k,:,:), nbgp )
2406          ENDDO
2407       ENDIF
2408
2409       IF ( water_pars_f%from_file )  THEN
2410          CALL resize_array_3d_real( water_pars_f%pars_xy,                     &
2411                                     0, water_pars_f%np-1,                     &
2412                                     nys, nyn, nxl, nxr )
2413          DO  k = 0, water_pars_f%np-1
2414             CALL exchange_horiz_2d( water_pars_f%pars_xy(k,:,:), nbgp )
2415          ENDDO
2416       ENDIF
2417
2418       IF ( root_area_density_lsm_f%from_file )  THEN
2419          CALL resize_array_3d_real( root_area_density_lsm_f%var,              &
2420                                     0, root_area_density_lsm_f%nz-1,          &
2421                                     nys, nyn, nxl, nxr )
2422          DO  k = 0, root_area_density_lsm_f%nz-1
2423             CALL exchange_horiz_2d( root_area_density_lsm_f%var(k,:,:), nbgp )
2424          ENDDO
2425       ENDIF
2426
2427       IF ( soil_pars_f%from_file )  THEN
2428          IF ( soil_pars_f%lod == 1 )  THEN
2429         
2430             CALL resize_array_3d_real( soil_pars_f%pars_xy,                   &
2431                                        0, soil_pars_f%np-1,                   &
2432                                        nys, nyn, nxl, nxr )
2433             DO  k = 0, soil_pars_f%np-1
2434                CALL exchange_horiz_2d( soil_pars_f%pars_xy(k,:,:), nbgp )
2435             ENDDO
2436             
2437          ELSEIF ( soil_pars_f%lod == 2 )  THEN
2438             CALL resize_array_4d_real( soil_pars_f%pars_xyz,                  &
2439                                        0, soil_pars_f%np-1,                   &
2440                                        0, soil_pars_f%nz-1,                   &
2441                                        nys, nyn, nxl, nxr )
2442
2443             DO  k2 = 0, soil_pars_f%nz-1
2444                DO  k = 0, soil_pars_f%np-1
2445                   CALL exchange_horiz_2d( soil_pars_f%pars_xyz(k,k2,:,:),     &
2446                                           nbgp )
2447                ENDDO
2448             ENDDO
2449          ENDIF
2450       ENDIF
2451
2452       IF ( pavement_subsurface_pars_f%from_file )  THEN         
2453          CALL resize_array_4d_real( pavement_subsurface_pars_f%pars_xyz,      &
2454                                     0, pavement_subsurface_pars_f%np-1,       &
2455                                     0, pavement_subsurface_pars_f%nz-1,       &
2456                                     nys, nyn, nxl, nxr )
2457
2458          DO  k2 = 0, pavement_subsurface_pars_f%nz-1
2459             DO  k = 0, pavement_subsurface_pars_f%np-1
2460                CALL exchange_horiz_2d(                                        &
2461                           pavement_subsurface_pars_f%pars_xyz(k,k2,:,:), nbgp )
2462             ENDDO
2463          ENDDO
2464       ENDIF
2465
2466    END SUBROUTINE netcdf_data_input_surface_data
2467
2468!------------------------------------------------------------------------------!
2469! Description:
2470! ------------
2471!> Reads uvem lookup table information.
2472!------------------------------------------------------------------------------!
2473    SUBROUTINE netcdf_data_input_uvem
2474       
2475       USE indices,                                                            &
2476           ONLY:  nxl, nxr, nyn, nys
2477
2478       IMPLICIT NONE
2479
2480       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names in static input file
2481
2482
2483       INTEGER(iwp) ::  id_uvem       !< NetCDF id of uvem lookup table input file
2484       INTEGER(iwp) ::  nli = 35      !< dimension length of lookup table in x
2485       INTEGER(iwp) ::  nlj =  9      !< dimension length of lookup table in y
2486       INTEGER(iwp) ::  nlk = 90      !< dimension length of lookup table in z
2487       INTEGER(iwp) ::  num_vars      !< number of variables in netcdf input file
2488!
2489!--    Input via uv exposure model lookup table input
2490       IF ( input_pids_uvem )  THEN
2491
2492#if defined ( __netcdf )
2493!
2494!--       Open file in read-only mode
2495          CALL open_read_file( TRIM( input_file_uvem ) //                    &
2496                               TRIM( coupling_char ), id_uvem )
2497!
2498!--       At first, inquire all variable names.
2499!--       This will be used to check whether an input variable exist or not.
2500          CALL inquire_num_variables( id_uvem, num_vars )
2501!
2502!--       Allocate memory to store variable names and inquire them.
2503          ALLOCATE( var_names(1:num_vars) )
2504          CALL inquire_variable_names( id_uvem, var_names )
2505!
2506!--       uvem integration
2507          IF ( check_existence( var_names, 'int_factors' ) )  THEN
2508             uvem_integration_f%from_file = .TRUE.
2509!
2510!--          Input 2D uvem integration.
2511             ALLOCATE ( uvem_integration_f%var(0:nlj,0:nli)  )
2512             
2513             CALL get_variable( id_uvem, 'int_factors', uvem_integration_f%var, 0, nli, 0, nlj )
2514          ELSE
2515             uvem_integration_f%from_file = .FALSE.
2516          ENDIF
2517!
2518!--       uvem irradiance
2519          IF ( check_existence( var_names, 'irradiance' ) )  THEN
2520             uvem_irradiance_f%from_file = .TRUE.
2521!
2522!--          Input 2D uvem irradiance.
2523             ALLOCATE ( uvem_irradiance_f%var(0:nlk, 0:2)  )
2524             
2525             CALL get_variable( id_uvem, 'irradiance', uvem_irradiance_f%var, 0, 2, 0, nlk )
2526          ELSE
2527             uvem_irradiance_f%from_file = .FALSE.
2528          ENDIF
2529!
2530!--       uvem porjection areas
2531          IF ( check_existence( var_names, 'projarea' ) )  THEN
2532             uvem_projarea_f%from_file = .TRUE.
2533!
2534!--          Input 3D uvem projection area (human geometgry)
2535             ALLOCATE ( uvem_projarea_f%var(0:2,0:nlj,0:nli)  )
2536           
2537             CALL get_variable( id_uvem, 'projarea', uvem_projarea_f%var, 0, nli, 0, nlj, 0, 2 )
2538          ELSE
2539             uvem_projarea_f%from_file = .FALSE.
2540          ENDIF
2541!
2542!--       uvem radiance
2543          IF ( check_existence( var_names, 'radiance' ) )  THEN
2544             uvem_radiance_f%from_file = .TRUE.
2545!
2546!--          Input 3D uvem radiance
2547             ALLOCATE ( uvem_radiance_f%var(0:nlk,0:nlj,0:nli)  )
2548             
2549             CALL get_variable( id_uvem, 'radiance', uvem_radiance_f%var, 0, nli, 0, nlj, 0, nlk )
2550          ELSE
2551             uvem_radiance_f%from_file = .FALSE.
2552          ENDIF
2553!
2554!--       Read building obstruction
2555          IF ( check_existence( var_names, 'obstruction' ) )  THEN
2556             building_obstruction_full%from_file = .TRUE.
2557!--          Input 3D uvem building obstruction
2558              ALLOCATE ( building_obstruction_full%var_3d(0:44,0:2,0:2) )
2559              CALL get_variable( id_uvem, 'obstruction', building_obstruction_full%var_3d,0, 2, 0, 2, 0, 44 )       
2560          ELSE
2561             building_obstruction_full%from_file = .FALSE.
2562          ENDIF
2563!
2564          IF ( check_existence( var_names, 'obstruction' ) )  THEN
2565             building_obstruction_f%from_file = .TRUE.
2566!
2567!--          Input 3D uvem building obstruction
2568             ALLOCATE ( building_obstruction_f%var_3d(0:44,nys:nyn,nxl:nxr) )
2569!
2570             CALL get_variable( id_uvem, 'obstruction', building_obstruction_f%var_3d,      &
2571                                nxl, nxr, nys, nyn, 0, 44 )       
2572          ELSE
2573             building_obstruction_f%from_file = .FALSE.
2574          ENDIF
2575!
2576!--       Close uvem lookup table input file
2577          CALL close_input_file( id_uvem )
2578#else
2579          CONTINUE
2580#endif
2581       ENDIF
2582    END SUBROUTINE netcdf_data_input_uvem
2583
2584!------------------------------------------------------------------------------!
2585! Description:
2586! ------------
2587!> Reads orography and building information.
2588!------------------------------------------------------------------------------!
2589    SUBROUTINE netcdf_data_input_topo
2590
2591       USE control_parameters,                                                 &
2592           ONLY:  message_string, topography
2593
2594       USE grid_variables,                                                     &
2595           ONLY:  dx, dy   
2596           
2597       USE indices,                                                            &
2598           ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb
2599
2600
2601       IMPLICIT NONE
2602
2603       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names  !< variable names in static input file
2604
2605
2606       INTEGER(iwp) ::  i             !< running index along x-direction
2607       INTEGER(iwp) ::  ii            !< running index for IO blocks
2608       INTEGER(iwp) ::  id_topo       !< NetCDF id of topograhy input file
2609       INTEGER(iwp) ::  j             !< running index along y-direction
2610       INTEGER(iwp) ::  num_vars      !< number of variables in netcdf input file
2611       INTEGER(iwp) ::  skip_n_rows   !< counting variable to skip rows while reading topography file
2612
2613       REAL(wp) ::  dum           !< dummy variable to skip columns while reading topography file
2614!
2615!--    CPU measurement
2616       CALL cpu_log( log_point_s(83), 'NetCDF/ASCII input topo', 'start' )
2617
2618!
2619!--    Input via palm-input data standard
2620       IF ( input_pids_static )  THEN
2621#if defined ( __netcdf )
2622!
2623!--       Open file in read-only mode
2624          CALL open_read_file( TRIM( input_file_static ) //                    &
2625                               TRIM( coupling_char ), id_topo )
2626!
2627!--       At first, inquire all variable names.
2628!--       This will be used to check whether an  input variable exist
2629!--       or not.
2630          CALL inquire_num_variables( id_topo, num_vars )
2631!
2632!--       Allocate memory to store variable names and inquire them.
2633          ALLOCATE( var_names(1:num_vars) )
2634          CALL inquire_variable_names( id_topo, var_names )
2635!
2636!--       Read x, y - dimensions. Only required for consistency checks.
2637          CALL netcdf_data_input_get_dimension_length( id_topo, dim_static%nx, 'x' )
2638          CALL netcdf_data_input_get_dimension_length( id_topo, dim_static%ny, 'y' )
2639          ALLOCATE( dim_static%x(0:dim_static%nx-1) )
2640          ALLOCATE( dim_static%y(0:dim_static%ny-1) )
2641          CALL get_variable( id_topo, 'x', dim_static%x )
2642          CALL get_variable( id_topo, 'y', dim_static%y )
2643!
2644!--       Check whether dimension size in input file matches the model dimensions
2645          IF ( dim_static%nx-1 /= nx  .OR.  dim_static%ny-1 /= ny )  THEN
2646             message_string = 'Static input file: horizontal dimension in ' // &
2647                              'x- and/or y-direction ' //                      &
2648                              'do not match the respective model dimension'
2649             CALL message( 'netcdf_data_input_mod', 'PA0548', 1, 2, 0, 6, 0 )
2650          ENDIF
2651!
2652!--       Check if grid spacing of provided input data matches the respective
2653!--       grid spacing in the model.
2654          IF ( ABS( dim_static%x(1) - dim_static%x(0) - dx ) > 10E-6_wp  .OR.  &
2655               ABS( dim_static%y(1) - dim_static%y(0) - dy ) > 10E-6_wp )  THEN
2656             message_string = 'Static input file: horizontal grid spacing ' // &
2657                              'in x- and/or y-direction ' //                   &
2658                              'do not match the respective model grid spacing.'
2659             CALL message( 'netcdf_data_input_mod', 'PA0549', 1, 2, 0, 6, 0 )
2660          ENDIF
2661!
2662!--       Terrain height. First, get variable-related _FillValue attribute
2663          IF ( check_existence( var_names, 'zt' ) )  THEN
2664             terrain_height_f%from_file = .TRUE.
2665             CALL get_attribute( id_topo, char_fill, terrain_height_f%fill,    &
2666                                 .FALSE., 'zt' )
2667!
2668!--          Input 2D terrain height.
2669             ALLOCATE ( terrain_height_f%var(nys:nyn,nxl:nxr)  )
2670             
2671             CALL get_variable( id_topo, 'zt', terrain_height_f%var,           &
2672                                nxl, nxr, nys, nyn )
2673
2674          ELSE
2675             terrain_height_f%from_file = .FALSE.
2676          ENDIF
2677
2678!
2679!--       Read building height. First, read its _FillValue attribute,
2680!--       as well as lod attribute
2681          buildings_f%from_file = .FALSE.
2682          IF ( check_existence( var_names, 'buildings_2d' ) )  THEN
2683             buildings_f%from_file = .TRUE.
2684             CALL get_attribute( id_topo, char_lod, buildings_f%lod,           &
2685                                 .FALSE., 'buildings_2d' )
2686
2687             CALL get_attribute( id_topo, char_fill, buildings_f%fill1,        &
2688                                 .FALSE., 'buildings_2d' )
2689
2690!
2691!--          Read 2D buildings
2692             IF ( buildings_f%lod == 1 )  THEN
2693                ALLOCATE ( buildings_f%var_2d(nys:nyn,nxl:nxr) )
2694
2695                CALL get_variable( id_topo, 'buildings_2d',                    &
2696                                   buildings_f%var_2d,                         &
2697                                   nxl, nxr, nys, nyn )
2698             ELSE
2699                message_string = 'NetCDF attribute lod ' //                    &
2700                                 '(level of detail) is not set ' //            &
2701                                 'properly for buildings_2d.'
2702                CALL message( 'netcdf_data_input_mod', 'PA0540',               &
2703                               1, 2, 0, 6, 0 )
2704             ENDIF
2705          ENDIF
2706!
2707!--       If available, also read 3D building information. If both are
2708!--       available, use 3D information.
2709          IF ( check_existence( var_names, 'buildings_3d' ) )  THEN
2710             buildings_f%from_file = .TRUE.
2711             CALL get_attribute( id_topo, char_lod, buildings_f%lod,           &
2712                                 .FALSE., 'buildings_3d' )     
2713
2714             CALL get_attribute( id_topo, char_fill, buildings_f%fill2,        &
2715                                 .FALSE., 'buildings_3d' )
2716
2717             CALL netcdf_data_input_get_dimension_length( id_topo,             &
2718                                                          buildings_f%nz, 'z' )
2719!
2720!--          Read 3D buildings
2721             IF ( buildings_f%lod == 2 )  THEN
2722                ALLOCATE( buildings_f%z(nzb:buildings_f%nz-1) )
2723                CALL get_variable( id_topo, 'z', buildings_f%z )
2724
2725                ALLOCATE( buildings_f%var_3d(nzb:buildings_f%nz-1,             &
2726                                             nys:nyn,nxl:nxr) )
2727                buildings_f%var_3d = 0
2728               
2729                CALL get_variable( id_topo, 'buildings_3d',                    &
2730                                   buildings_f%var_3d,                         &
2731                                   nxl, nxr, nys, nyn, 0, buildings_f%nz-1 )
2732             ELSE
2733                message_string = 'NetCDF attribute lod ' //                    &
2734                                 '(level of detail) is not set ' //            &
2735                                 'properly for buildings_3d.'
2736                CALL message( 'netcdf_data_input_mod', 'PA0541',               &
2737                               1, 2, 0, 6, 0 )
2738             ENDIF
2739          ENDIF
2740!
2741!--       Read building IDs and its FillValue attribute. Further required
2742!--       for mapping buildings on top of orography.
2743          IF ( check_existence( var_names, 'building_id' ) )  THEN
2744             building_id_f%from_file = .TRUE.
2745             CALL get_attribute( id_topo, char_fill,                           &
2746                                 building_id_f%fill, .FALSE.,                  &
2747                                 'building_id' )
2748
2749             ALLOCATE ( building_id_f%var(nys:nyn,nxl:nxr) )
2750             
2751             CALL get_variable( id_topo, 'building_id', building_id_f%var,     &
2752                                nxl, nxr, nys, nyn )
2753          ELSE
2754             building_id_f%from_file = .FALSE.
2755          ENDIF
2756!
2757!--       Read building_type and required attributes.
2758          IF ( check_existence( var_names, 'building_type' ) )  THEN
2759             building_type_f%from_file = .TRUE.
2760             CALL get_attribute( id_topo, char_fill,                           &
2761                                 building_type_f%fill, .FALSE.,                &
2762                                 'building_type' )
2763
2764             ALLOCATE ( building_type_f%var(nys:nyn,nxl:nxr) )
2765
2766             CALL get_variable( id_topo, 'building_type', building_type_f%var, &
2767                                nxl, nxr, nys, nyn )
2768
2769          ELSE
2770             building_type_f%from_file = .FALSE.
2771          ENDIF
2772!
2773!--       Close topography input file
2774          CALL close_input_file( id_topo )
2775#else
2776          CONTINUE
2777#endif
2778!
2779!--    ASCII input
2780       ELSEIF ( TRIM( topography ) == 'read_from_file' )  THEN
2781             
2782          DO  ii = 0, io_blocks-1
2783             IF ( ii == io_group )  THEN
2784
2785                OPEN( 90, FILE='TOPOGRAPHY_DATA'//TRIM( coupling_char ),       &
2786                      STATUS='OLD', FORM='FORMATTED', ERR=10 )
2787!
2788!--             Read topography PE-wise. Rows are read from nyn to nys, columns
2789!--             are read from nxl to nxr. At first, ny-nyn rows need to be skipped.
2790                skip_n_rows = 0
2791                DO WHILE ( skip_n_rows < ny - nyn )
2792                   READ( 90, * )
2793                   skip_n_rows = skip_n_rows + 1
2794                ENDDO
2795!
2796!--             Read data from nyn to nys and nxl to nxr. Therefore, skip
2797!--             column until nxl-1 is reached
2798                ALLOCATE ( buildings_f%var_2d(nys:nyn,nxl:nxr) )
2799                DO  j = nyn, nys, -1
2800                   READ( 90, *, ERR=11, END=11 )                               &
2801                                   ( dum, i = 0, nxl-1 ),                      &
2802                                   ( buildings_f%var_2d(j,i), i = nxl, nxr )
2803                ENDDO
2804
2805                GOTO 12
2806
2807 10             message_string = 'file TOPOGRAPHY_DATA'//                      &
2808                                 TRIM( coupling_char )// ' does not exist'
2809                CALL message( 'netcdf_data_input_mod', 'PA0208', 1, 2, 0, 6, 0 )
2810
2811 11             message_string = 'errors in file TOPOGRAPHY_DATA'//            &
2812                                 TRIM( coupling_char )
2813                CALL message( 'netcdf_data_input_mod', 'PA0209', 2, 2, 0, 6, 0 )
2814
2815 12             CLOSE( 90 )
2816                buildings_f%from_file = .TRUE.
2817
2818             ENDIF
2819#if defined( __parallel )
2820             CALL MPI_BARRIER( comm2d, ierr )
2821#endif
2822          ENDDO
2823
2824       ENDIF
2825!
2826!--    End of CPU measurement
2827       CALL cpu_log( log_point_s(83), 'NetCDF/ASCII input topo', 'stop' )
2828!
2829!--    Check for minimum requirement to setup building topography. If buildings
2830!--    are provided, also an ID and a type are required.
2831!--    Note, doing this check in check_parameters
2832!--    will be too late (data will be used for grid inititialization before).
2833       IF ( input_pids_static )  THEN
2834          IF ( buildings_f%from_file  .AND.                                    &
2835               .NOT. building_id_f%from_file )  THEN
2836             message_string = 'If building heights are prescribed in ' //      &
2837                              'static input file, also an ID is required.'
2838             CALL message( 'netcdf_data_input_mod', 'PA0542', 1, 2, 0, 6, 0 )
2839          ENDIF
2840       ENDIF
2841!
2842!--    In case no terrain height is provided by static input file, allocate
2843!--    array nevertheless and set terrain height to 0, which simplifies
2844!--    topography initialization.
2845       IF ( .NOT. terrain_height_f%from_file )  THEN
2846          ALLOCATE ( terrain_height_f%var(nys:nyn,nxl:nxr) )
2847          terrain_height_f%var = 0.0_wp
2848       ENDIF
2849!
2850!--    Finally, exchange 1 ghost point for building ID and type.
2851!--    In case of non-cyclic boundary conditions set Neumann conditions at the
2852!--    lateral boundaries.
2853       IF ( building_id_f%from_file )  THEN
2854          CALL resize_array_2d_int32( building_id_f%var, nys, nyn, nxl, nxr )
2855          CALL exchange_horiz_2d_int( building_id_f%var, nys, nyn, nxl, nxr,   &
2856                                      nbgp )
2857       ENDIF
2858
2859       IF ( building_type_f%from_file )  THEN
2860          CALL resize_array_2d_int8( building_type_f%var, nys, nyn, nxl, nxr )
2861          CALL exchange_horiz_2d_byte( building_type_f%var, nys, nyn, nxl, nxr,   &
2862                                       nbgp )
2863       ENDIF
2864
2865    END SUBROUTINE netcdf_data_input_topo
2866
2867!------------------------------------------------------------------------------!
2868! Description:
2869! ------------
2870!> Reads initialization data of u, v, w, pt, q, geostrophic wind components,
2871!> as well as soil moisture and soil temperature, derived from larger-scale
2872!> model (COSMO) by Inifor.
2873!------------------------------------------------------------------------------!
2874    SUBROUTINE netcdf_data_input_init_3d
2875
2876       USE arrays_3d,                                                          &
2877           ONLY:  q, pt, u, v, w, zu, zw
2878
2879       USE control_parameters,                                                 &
2880           ONLY:  air_chemistry, bc_lr_cyc, bc_ns_cyc, humidity,               &
2881                  message_string, neutral
2882
2883       USE indices,                                                            &
2884           ONLY:  nx, nxl, nxlu, nxr, ny, nyn, nys, nysv, nzb, nz, nzt
2885
2886       IMPLICIT NONE
2887
2888       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names
2889
2890       LOGICAL      ::  dynamic_3d = .TRUE. !< flag indicating that 3D data is read from dynamic file
2891       
2892       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
2893       INTEGER(iwp) ::  n          !< running index for chemistry variables
2894       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
2895
2896       LOGICAL      ::  check_passed !< flag indicating if a check passed
2897
2898!
2899!--    Skip routine if no input file with dynamic input data is available.
2900       IF ( .NOT. input_pids_dynamic )  RETURN
2901!
2902!--    Please note, Inifor is designed to provide initial data for u and v for
2903!--    the prognostic grid points in case of lateral Dirichlet conditions.
2904!--    This means that Inifor provides data from nxlu:nxr (for u) and
2905!--    from nysv:nyn (for v) at the left and south domain boundary, respectively.
2906!--    However, as work-around for the moment, PALM will run with cyclic
2907!--    conditions and will be initialized with data provided by Inifor
2908!--    boundaries in case of Dirichlet.
2909!--    Hence, simply set set nxlu/nysv to 1 (will be reset to its original value
2910!--    at the end of this routine.
2911       IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = 1
2912       IF ( bc_ns_cyc  .AND.  nys == 0 )  nysv = 1
2913
2914!
2915!--    CPU measurement
2916       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'start' )
2917
2918#if defined ( __netcdf )
2919!
2920!--    Open file in read-only mode
2921       CALL open_read_file( TRIM( input_file_dynamic ) //                      &
2922                            TRIM( coupling_char ), id_dynamic )
2923
2924!
2925!--    At first, inquire all variable names.
2926       CALL inquire_num_variables( id_dynamic, num_vars )
2927!
2928!--    Allocate memory to store variable names.
2929       ALLOCATE( var_names(1:num_vars) )
2930       CALL inquire_variable_names( id_dynamic, var_names )
2931!
2932!--    Read vertical dimension of scalar und w grid.
2933       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nzu, 'z'     )
2934       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nzw, 'zw'    )
2935!
2936!--    Read also the horizontal dimensions. These are used just used fo
2937!--    checking the compatibility with the PALM grid before reading.
2938       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nx,  'x'  )
2939       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nxu, 'xu' )
2940       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%ny,  'y'  )
2941       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nyv, 'yv' )
2942
2943!
2944!--    Check for correct horizontal and vertical dimension. Please note,
2945!--    checks are performed directly here and not called from
2946!--    check_parameters as some varialbes are still not allocated there.
2947!--    Moreover, please note, u- and v-grid has 1 grid point less on
2948!--    Inifor grid.
2949       IF ( init_3d%nx-1 /= nx  .OR.  init_3d%nxu-1 /= nx - 1  .OR.            &
2950            init_3d%ny-1 /= ny  .OR.  init_3d%nyv-1 /= ny - 1 )  THEN
2951          message_string = 'Number of inifor horizontal grid points  '//       &
2952                           'does not match the number of numeric grid '//      &
2953                           'points.'
2954          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
2955       ENDIF
2956
2957       IF ( init_3d%nzu /= nz )  THEN
2958          message_string = 'Number of inifor vertical grid points ' //         &
2959                           'does not match the number of numeric grid '//      &
2960                           'points.'
2961          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
2962       ENDIF
2963!
2964!--    Read vertical dimensions. Later, these are required for eventual
2965!--    inter- and extrapolations of the initialization data.
2966       IF ( check_existence( var_names, 'z' ) )  THEN
2967          ALLOCATE( init_3d%zu_atmos(1:init_3d%nzu) )
2968          CALL get_variable( id_dynamic, 'z', init_3d%zu_atmos )
2969       ENDIF
2970       IF ( check_existence( var_names, 'zw' ) )  THEN
2971          ALLOCATE( init_3d%zw_atmos(1:init_3d%nzw) )
2972          CALL get_variable( id_dynamic, 'zw', init_3d%zw_atmos )
2973       ENDIF
2974!
2975!--    Check for consistency between vertical coordinates in dynamic
2976!--    driver and numeric grid.
2977!--    Please note, depending on compiler options both may be
2978!--    equal up to a certain threshold, and differences between
2979!--    the numeric grid and vertical coordinate in the driver can built-
2980!--    up to 10E-1-10E-0 m. For this reason, the check is performed not
2981!--    for exactly matching values.
2982       IF ( ANY( ABS( zu(1:nzt)   - init_3d%zu_atmos(1:init_3d%nzu) )    &
2983                      > 10E-1 )  .OR.                                    &
2984            ANY( ABS( zw(1:nzt-1) - init_3d%zw_atmos(1:init_3d%nzw) )    &
2985                      > 10E-1 ) )  THEN
2986          message_string = 'Vertical grid in dynamic driver does not '// &
2987                           'match the numeric grid.'
2988          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
2989       ENDIF
2990!
2991!--    Read initial geostrophic wind components at
2992!--    t = 0 (index 1 in file).
2993       IF ( check_existence( var_names, 'ls_forcing_ug' ) )  THEN
2994          ALLOCATE( init_3d%ug_init(nzb:nzt+1) )
2995          init_3d%ug_init = 0.0_wp
2996
2997          CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', 1,          &
2998                                init_3d%ug_init(1:nzt) )
2999!
3000!--       Set top-boundary condition (Neumann)
3001          init_3d%ug_init(nzt+1) = init_3d%ug_init(nzt)
3002
3003          init_3d%from_file_ug = .TRUE.
3004       ELSE
3005          init_3d%from_file_ug = .FALSE.
3006       ENDIF
3007       IF ( check_existence( var_names, 'ls_forcing_vg' ) )  THEN
3008          ALLOCATE( init_3d%vg_init(nzb:nzt+1) )
3009          init_3d%vg_init = 0.0_wp
3010
3011          CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', 1,          &
3012                                init_3d%vg_init(1:nzt) )
3013!
3014!--       Set top-boundary condition (Neumann)
3015          init_3d%vg_init(nzt+1) = init_3d%vg_init(nzt)
3016
3017          init_3d%from_file_vg = .TRUE.
3018       ELSE
3019          init_3d%from_file_vg = .FALSE.
3020       ENDIF
3021!
3022!--    Read inital 3D data of u, v, w, pt and q,
3023!--    derived from COSMO model. Read PE-wise yz-slices.
3024!--    Please note, the u-, v- and w-component are defined on different
3025!--    grids with one element less in the x-, y-,
3026!--    and z-direction, respectively. Hence, reading is subdivided
3027!--    into separate loops. 
3028!--    Read u-component
3029       IF ( check_existence( var_names, 'init_atmosphere_u' ) )  THEN
3030!
3031!--       Read attributes for the fill value and level-of-detail
3032          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_u,           &
3033                              .FALSE., 'init_atmosphere_u' )
3034          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_u,             &
3035                              .FALSE., 'init_atmosphere_u' )
3036!
3037!--       level-of-detail 1 - read initialization profile
3038          IF ( init_3d%lod_u == 1 )  THEN
3039             ALLOCATE( init_3d%u_init(nzb:nzt+1) )
3040             init_3d%u_init = 0.0_wp
3041
3042             CALL get_variable( id_dynamic, 'init_atmosphere_u',               &
3043                                init_3d%u_init(nzb+1:nzt) )
3044!
3045!--          Set top-boundary condition (Neumann)
3046             init_3d%u_init(nzt+1) = init_3d%u_init(nzt)
3047!
3048!--       level-of-detail 2 - read 3D initialization data
3049          ELSEIF ( init_3d%lod_u == 2 )  THEN
3050             CALL get_variable( id_dynamic, 'init_atmosphere_u',               &
3051                                u(nzb+1:nzt,nys:nyn,nxlu:nxr),                 &
3052                                nxlu, nys+1, nzb+1,                            &
3053                                nxr-nxlu+1, nyn-nys+1, init_3d%nzu,            &
3054                                dynamic_3d )
3055!
3056!--          Set value at leftmost model grid point nxl = 0. This is because
3057!--          Inifor provides data only from 1:nx-1 since it assumes non-cyclic
3058!--          conditions.
3059             IF ( nxl == 0 )                                                   &
3060                u(nzb+1:nzt,nys:nyn,nxl) = u(nzb+1:nzt,nys:nyn,nxlu)
3061!
3062!--          Set bottom and top-boundary
3063             u(nzb,:,:)   = u(nzb+1,:,:)
3064             u(nzt+1,:,:) = u(nzt,:,:)
3065             
3066          ENDIF
3067          init_3d%from_file_u = .TRUE.
3068       ELSE
3069          message_string = 'Missing initial data for u-component'
3070          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
3071       ENDIF
3072!
3073!--    Read v-component
3074       IF ( check_existence( var_names, 'init_atmosphere_v' ) )  THEN
3075!
3076!--       Read attributes for the fill value and level-of-detail
3077          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_v,           &
3078                              .FALSE., 'init_atmosphere_v' )
3079          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_v,             &
3080                              .FALSE., 'init_atmosphere_v' )
3081!
3082!--       level-of-detail 1 - read initialization profile
3083          IF ( init_3d%lod_v == 1 )  THEN
3084             ALLOCATE( init_3d%v_init(nzb:nzt+1) )
3085             init_3d%v_init = 0.0_wp
3086
3087             CALL get_variable( id_dynamic, 'init_atmosphere_v',               &
3088                                init_3d%v_init(nzb+1:nzt) )
3089!
3090!--          Set top-boundary condition (Neumann)
3091             init_3d%v_init(nzt+1) = init_3d%v_init(nzt)
3092!
3093!--       level-of-detail 2 - read 3D initialization data
3094          ELSEIF ( init_3d%lod_v == 2 )  THEN
3095         
3096             CALL get_variable( id_dynamic, 'init_atmosphere_v',               &
3097                                v(nzb+1:nzt,nysv:nyn,nxl:nxr),                 &
3098                                nxl+1, nysv, nzb+1,                            &
3099                                nxr-nxl+1, nyn-nysv+1, init_3d%nzu,            &
3100                                dynamic_3d )
3101!
3102!--          Set value at southmost model grid point nys = 0. This is because
3103!--          Inifor provides data only from 1:ny-1 since it assumes non-cyclic
3104!--          conditions.
3105             IF ( nys == 0 )                                                   &
3106                v(nzb+1:nzt,nys,nxl:nxr) = v(nzb+1:nzt,nysv,nxl:nxr)                               
3107!
3108!--          Set bottom and top-boundary
3109             v(nzb,:,:)   = v(nzb+1,:,:)
3110             v(nzt+1,:,:) = v(nzt,:,:)
3111             
3112          ENDIF
3113          init_3d%from_file_v = .TRUE.
3114       ELSE
3115          message_string = 'Missing initial data for v-component'
3116          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
3117       ENDIF
3118!
3119!--    Read w-component
3120       IF ( check_existence( var_names, 'init_atmosphere_w' ) )  THEN
3121!
3122!--       Read attributes for the fill value and level-of-detail
3123          CALL get_attribute( id_dynamic, char_fill, init_3d%fill_w,           &
3124                              .FALSE., 'init_atmosphere_w' )
3125          CALL get_attribute( id_dynamic, char_lod, init_3d%lod_w,             &
3126                              .FALSE., 'init_atmosphere_w' )
3127!
3128!--       level-of-detail 1 - read initialization profile
3129          IF ( init_3d%lod_w == 1 )  THEN
3130             ALLOCATE( init_3d%w_init(nzb:nzt+1) )
3131             init_3d%w_init = 0.0_wp
3132
3133             CALL get_variable( id_dynamic, 'init_atmosphere_w',               &
3134                                init_3d%w_init(nzb+1:nzt-1) )
3135!
3136!--          Set top-boundary condition (Neumann)
3137             init_3d%w_init(nzt:nzt+1) = init_3d%w_init(nzt-1)
3138!
3139!--       level-of-detail 2 - read 3D initialization data
3140          ELSEIF ( init_3d%lod_w == 2 )  THEN
3141
3142             CALL get_variable( id_dynamic, 'init_atmosphere_w',                &
3143                                w(nzb+1:nzt-1,nys:nyn,nxl:nxr),                 &
3144                                nxl+1, nys+1, nzb+1,                            &
3145                                nxr-nxl+1, nyn-nys+1, init_3d%nzw,              &
3146                                dynamic_3d )
3147!
3148!--          Set bottom and top-boundary                               
3149             w(nzb,:,:)   = 0.0_wp 
3150             w(nzt,:,:)   = w(nzt-1,:,:)
3151             w(nzt+1,:,:) = w(nzt-1,:,:)
3152
3153          ENDIF
3154          init_3d%from_file_w = .TRUE.
3155       ELSE
3156          message_string = 'Missing initial data for w-component'
3157          CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
3158       ENDIF
3159!
3160!--    Read potential temperature
3161       IF ( .NOT. neutral )  THEN
3162          IF ( check_existence( var_names, 'init_atmosphere_pt' ) )  THEN
3163!
3164!--          Read attributes for the fill value and level-of-detail
3165             CALL get_attribute( id_dynamic, char_fill, init_3d%fill_pt,       &
3166                                 .FALSE., 'init_atmosphere_pt' )
3167             CALL get_attribute( id_dynamic, char_lod, init_3d%lod_pt,         &
3168                                 .FALSE., 'init_atmosphere_pt' )
3169!
3170!--          level-of-detail 1 - read initialization profile
3171             IF ( init_3d%lod_pt == 1 )  THEN
3172                ALLOCATE( init_3d%pt_init(nzb:nzt+1) )
3173
3174                CALL get_variable( id_dynamic, 'init_atmosphere_pt',           &
3175                                   init_3d%pt_init(nzb+1:nzt) )
3176!
3177!--             Set Neumann top and surface boundary condition for initial
3178!--             profil
3179                init_3d%pt_init(nzb)   = init_3d%pt_init(nzb+1)
3180                init_3d%pt_init(nzt+1) = init_3d%pt_init(nzt)
3181!
3182!--          level-of-detail 2 - read 3D initialization data
3183             ELSEIF ( init_3d%lod_pt == 2 )  THEN
3184
3185                CALL get_variable( id_dynamic, 'init_atmosphere_pt',           &
3186                                   pt(nzb+1:nzt,nys:nyn,nxl:nxr),              &
3187                                   nxl+1, nys+1, nzb+1,                        &
3188                                   nxr-nxl+1, nyn-nys+1, init_3d%nzu,          &
3189                                   dynamic_3d )
3190                                   
3191!
3192!--             Set bottom and top-boundary
3193                pt(nzb,:,:)   = pt(nzb+1,:,:)
3194                pt(nzt+1,:,:) = pt(nzt,:,:)             
3195
3196             ENDIF
3197             init_3d%from_file_pt = .TRUE.
3198          ELSE
3199             message_string = 'Missing initial data for ' //                   &
3200                              'potential temperature'
3201             CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
3202          ENDIF
3203       ENDIF
3204!
3205!--    Read mixing ratio
3206       IF ( humidity )  THEN
3207          IF ( check_existence( var_names, 'init_atmosphere_qv' ) )  THEN
3208!
3209!--          Read attributes for the fill value and level-of-detail
3210             CALL get_attribute( id_dynamic, char_fill, init_3d%fill_q,        &
3211                                 .FALSE., 'init_atmosphere_qv' )
3212             CALL get_attribute( id_dynamic, char_lod, init_3d%lod_q,          &
3213                                 .FALSE., 'init_atmosphere_qv' )
3214!
3215!--          level-of-detail 1 - read initialization profile
3216             IF ( init_3d%lod_q == 1 )  THEN
3217                ALLOCATE( init_3d%q_init(nzb:nzt+1) )
3218
3219                CALL get_variable( id_dynamic, 'init_atmosphere_qv',           &
3220                                    init_3d%q_init(nzb+1:nzt) )
3221!
3222!--             Set bottom and top boundary condition (Neumann)
3223                init_3d%q_init(nzb)   = init_3d%q_init(nzb+1)
3224                init_3d%q_init(nzt+1) = init_3d%q_init(nzt)
3225!
3226!--          level-of-detail 2 - read 3D initialization data
3227             ELSEIF ( init_3d%lod_q == 2 )  THEN
3228             
3229                CALL get_variable( id_dynamic, 'init_atmosphere_qv',           &
3230                                   q(nzb+1:nzt,nys:nyn,nxl:nxr),               &
3231                                   nxl+1, nys+1, nzb+1,                        &
3232                                   nxr-nxl+1, nyn-nys+1, init_3d%nzu,          &
3233                                   dynamic_3d )
3234                                   
3235!
3236!--             Set bottom and top-boundary
3237                q(nzb,:,:)   = q(nzb+1,:,:)
3238                q(nzt+1,:,:) = q(nzt,:,:)
3239               
3240             ENDIF
3241             init_3d%from_file_q = .TRUE.
3242          ELSE
3243             message_string = 'Missing initial data for ' //                   &
3244                              'mixing ratio'
3245             CALL message( 'netcdf_data_input_mod', 'PA0544', 1, 2, 0, 6, 0 )
3246          ENDIF
3247       ENDIF       
3248!
3249!--    Read chemistry variables.
3250!--    Please note, for the moment, only LOD=1 is allowed
3251       IF ( air_chemistry )  THEN
3252!
3253!--       Allocate chemistry input profiles, as well as arrays for fill values
3254!--       and LOD's.
3255          ALLOCATE( init_3d%chem_init(nzb:nzt+1,                               &
3256                                      1:UBOUND(init_3d%var_names_chem, 1 )) )
3257          ALLOCATE( init_3d%fill_chem(1:UBOUND(init_3d%var_names_chem, 1)) )   
3258          ALLOCATE( init_3d%lod_chem(1:UBOUND(init_3d%var_names_chem, 1))  ) 
3259         
3260          DO  n = 1, UBOUND(init_3d%var_names_chem, 1)
3261             IF ( check_existence( var_names,                                  &
3262                                   TRIM( init_3d%var_names_chem(n) ) ) )  THEN
3263!
3264!--             Read attributes for the fill value and level-of-detail
3265                CALL get_attribute( id_dynamic, char_fill,                     &
3266                                    init_3d%fill_chem(n),                      &
3267                                    .FALSE.,                                   &
3268                                    TRIM( init_3d%var_names_chem(n) ) )
3269                CALL get_attribute( id_dynamic, char_lod,                      &
3270                                    init_3d%lod_chem(n),                       &
3271                                    .FALSE.,                                   &
3272                                    TRIM( init_3d%var_names_chem(n) ) )
3273!
3274!--             Give message that only LOD=1 is allowed.
3275                IF ( init_3d%lod_chem(n) /= 1 )  THEN               
3276                   message_string = 'For chemistry variables only LOD=1 is ' //&
3277                                    'allowed.'
3278                   CALL message( 'netcdf_data_input_mod', 'PA0586',            &
3279                                 1, 2, 0, 6, 0 )
3280                ENDIF
3281!
3282!--             level-of-detail 1 - read initialization profile
3283                CALL get_variable( id_dynamic,                                 &
3284                                   TRIM( init_3d%var_names_chem(n) ),          &
3285                                   init_3d%chem_init(nzb+1:nzt,n) )
3286!
3287!--             Set bottom and top boundary condition (Neumann)
3288                init_3d%chem_init(nzb,n)   = init_3d%chem_init(nzb+1,n)
3289                init_3d%chem_init(nzt+1,n) = init_3d%chem_init(nzt,n)
3290               
3291                init_3d%from_file_chem(n) = .TRUE.
3292             ENDIF
3293          ENDDO
3294       ENDIF
3295!
3296!--    Close input file
3297       CALL close_input_file( id_dynamic )
3298#endif
3299!
3300!--    End of CPU measurement
3301       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'stop' )
3302!
3303!--    Finally, check if the input data has any fill values. Please note,
3304!--    checks depend on the LOD of the input data.
3305       IF ( init_3d%from_file_u )  THEN
3306          check_passed = .TRUE.
3307          IF ( init_3d%lod_u == 1 )  THEN
3308             IF ( ANY( init_3d%u_init(nzb+1:nzt+1) == init_3d%fill_u ) )       &
3309                check_passed = .FALSE.
3310          ELSEIF ( init_3d%lod_u == 2 )  THEN
3311             IF ( ANY( u(nzb+1:nzt+1,nys:nyn,nxlu:nxr) == init_3d%fill_u ) )   &
3312                check_passed = .FALSE.
3313          ENDIF
3314          IF ( .NOT. check_passed )  THEN
3315             message_string = 'NetCDF input for init_atmosphere_u must ' //    &
3316                              'not contain any _FillValues'
3317             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
3318          ENDIF
3319       ENDIF
3320
3321       IF ( init_3d%from_file_v )  THEN
3322          check_passed = .TRUE.
3323          IF ( init_3d%lod_v == 1 )  THEN
3324             IF ( ANY( init_3d%v_init(nzb+1:nzt+1) == init_3d%fill_v ) )       &
3325                check_passed = .FALSE.
3326          ELSEIF ( init_3d%lod_v == 2 )  THEN
3327             IF ( ANY( v(nzb+1:nzt+1,nysv:nyn,nxl:nxr) == init_3d%fill_v ) )   &
3328                check_passed = .FALSE.
3329          ENDIF
3330          IF ( .NOT. check_passed )  THEN
3331             message_string = 'NetCDF input for init_atmosphere_v must ' //    &
3332                              'not contain any _FillValues'
3333             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
3334          ENDIF
3335       ENDIF
3336
3337       IF ( init_3d%from_file_w )  THEN
3338          check_passed = .TRUE.
3339          IF ( init_3d%lod_w == 1 )  THEN
3340             IF ( ANY( init_3d%w_init(nzb+1:nzt) == init_3d%fill_w ) )         &
3341                check_passed = .FALSE.
3342          ELSEIF ( init_3d%lod_w == 2 )  THEN
3343             IF ( ANY( w(nzb+1:nzt,nys:nyn,nxl:nxr) == init_3d%fill_w ) )      &
3344                check_passed = .FALSE.
3345          ENDIF
3346          IF ( .NOT. check_passed )  THEN
3347             message_string = 'NetCDF input for init_atmosphere_w must ' //    &
3348                              'not contain any _FillValues'
3349             CALL message( 'netcdf_data_input_mod', 'PA0545', 2, 2, 0, 6, 0 )
3350          ENDIF
3351       ENDIF
3352
3353       IF ( init_3d%from_file_pt )  THEN
3354          check_passed = .TRUE.
3355          IF ( init_3d%lod_pt == 1 )  THEN
3356             IF ( ANY( init_3d%pt_init(nzb+1:nzt+1) == init_3d%fill_pt ) )     &
3357                check_passed = .FALSE.
3358          ELSEIF ( init_3d%lod_pt == 2 )  THEN
3359             IF ( ANY( pt(nzb+1:nzt+1,nys:nyn,nxl:nxr) == init_3d%fill_pt ) )  &
3360                check_passed = .FALSE.
3361          ENDIF
3362          IF ( .NOT. check_passed )  THEN
3363             message_string = 'NetCDF input for init_atmosphere_pt 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_q )  THEN
3370          check_passed = .TRUE.
3371          IF ( init_3d%lod_q == 1 )  THEN
3372             IF ( ANY( init_3d%q_init(nzb+1:nzt+1) == init_3d%fill_q ) )       &
3373                check_passed = .FALSE.
3374          ELSEIF ( init_3d%lod_q == 2 )  THEN
3375             IF ( ANY( q(nzb+1:nzt+1,nys:nyn,nxl:nxr) == init_3d%fill_q ) )    &
3376                check_passed = .FALSE.
3377          ENDIF
3378          IF ( .NOT. check_passed )  THEN
3379             message_string = 'NetCDF input for init_atmosphere_q 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!--    Workaround for cyclic conditions. Please see above for further explanation.
3386       IF ( bc_lr_cyc  .AND.  nxl == 0 )  nxlu = nxl
3387       IF ( bc_ns_cyc  .AND.  nys == 0 )  nysv = nys
3388
3389    END SUBROUTINE netcdf_data_input_init_3d
3390   
3391!------------------------------------------------------------------------------!
3392! Description:
3393! ------------
3394!> Reads initialization data of u, v, w, pt, q, geostrophic wind components,
3395!> as well as soil moisture and soil temperature, derived from larger-scale
3396!> model (COSMO) by Inifor.
3397!------------------------------------------------------------------------------!
3398    SUBROUTINE netcdf_data_input_init_lsm
3399
3400       USE control_parameters,                                                 &
3401           ONLY:  message_string
3402
3403       USE indices,                                                            &
3404           ONLY:  nx, nxl, nxr, ny, nyn, nys
3405
3406       IMPLICIT NONE
3407
3408       CHARACTER(LEN=100), DIMENSION(:), ALLOCATABLE ::  var_names !< string containing all variables on file
3409     
3410       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
3411       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
3412
3413!
3414!--    Skip routine if no input file with dynamic input data is available.
3415       IF ( .NOT. input_pids_dynamic )  RETURN
3416!
3417!--    CPU measurement
3418       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'start' )
3419
3420#if defined ( __netcdf )
3421!
3422!--    Open file in read-only mode
3423       CALL open_read_file( TRIM( input_file_dynamic ) //                      &
3424                            TRIM( coupling_char ), id_dynamic )
3425
3426!
3427!--    At first, inquire all variable names.
3428       CALL inquire_num_variables( id_dynamic, num_vars )
3429!
3430!--    Allocate memory to store variable names.
3431       ALLOCATE( var_names(1:num_vars) )
3432       CALL inquire_variable_names( id_dynamic, var_names )
3433!
3434!--    Read vertical dimension for soil depth.
3435       IF ( check_existence( var_names, 'zsoil' ) )                            &
3436          CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nzs,&
3437                                                       'zsoil' )
3438!
3439!--    Read also the horizontal dimensions required for soil initialization.
3440!--    Please note, in case of non-nested runs or in case of root domain,
3441!--    these data is already available, but will be read again for the sake
3442!--    of clearness.
3443       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%nx,    &
3444                                                    'x'  )
3445       CALL netcdf_data_input_get_dimension_length( id_dynamic, init_3d%ny,    &
3446                                                    'y'  )
3447!
3448!--    Check for correct horizontal and vertical dimension. Please note,
3449!--    in case of non-nested runs or in case of root domain, these checks
3450!--    are already performed
3451       IF ( init_3d%nx-1 /= nx  .OR.  init_3d%ny-1 /= ny )  THEN
3452          message_string = 'Number of inifor horizontal grid points  '//       &
3453                           'does not match the number of numeric grid points.'
3454          CALL message( 'netcdf_data_input_mod', 'PA0543', 1, 2, 0, 6, 0 )
3455       ENDIF
3456!
3457!--    Read vertical dimensions. Later, these are required for eventual
3458!--    inter- and extrapolations of the initialization data.
3459       IF ( check_existence( var_names, 'zsoil' ) )  THEN
3460          ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )
3461          CALL get_variable( id_dynamic, 'zsoil', init_3d%z_soil )
3462       ENDIF
3463!
3464!--    Read initial data for soil moisture
3465       IF ( check_existence( var_names, 'init_soil_m' ) )  THEN
3466!
3467!--       Read attributes for the fill value and level-of-detail
3468          CALL get_attribute( id_dynamic, char_fill,                           &
3469                              init_3d%fill_msoil,                              &
3470                              .FALSE., 'init_soil_m' )
3471          CALL get_attribute( id_dynamic, char_lod,                            &
3472                              init_3d%lod_msoil,                               &
3473                              .FALSE., 'init_soil_m' )
3474!
3475!--       level-of-detail 1 - read initialization profile
3476          IF ( init_3d%lod_msoil == 1 )  THEN
3477             ALLOCATE( init_3d%msoil_1d(0:init_3d%nzs-1) )
3478
3479             CALL get_variable( id_dynamic, 'init_soil_m',                     &
3480                                init_3d%msoil_1d(0:init_3d%nzs-1) )
3481!
3482!--       level-of-detail 2 - read 3D initialization data
3483          ELSEIF ( init_3d%lod_msoil == 2 )  THEN
3484             ALLOCATE ( init_3d%msoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
3485
3486            CALL get_variable( id_dynamic, 'init_soil_m',                      &   
3487                             init_3d%msoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
3488                             nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
3489
3490          ENDIF
3491          init_3d%from_file_msoil = .TRUE.
3492       ENDIF
3493!
3494!--    Read soil temperature
3495       IF ( check_existence( var_names, 'init_soil_t' ) )  THEN
3496!
3497!--       Read attributes for the fill value and level-of-detail
3498          CALL get_attribute( id_dynamic, char_fill,                           &
3499                              init_3d%fill_tsoil,                              &
3500                              .FALSE., 'init_soil_t' )
3501          CALL get_attribute( id_dynamic, char_lod,                            &
3502                              init_3d%lod_tsoil,                               &
3503                              .FALSE., 'init_soil_t' )
3504!
3505!--       level-of-detail 1 - read initialization profile
3506          IF ( init_3d%lod_tsoil == 1 )  THEN
3507             ALLOCATE( init_3d%tsoil_1d(0:init_3d%nzs-1) )
3508
3509             CALL get_variable( id_dynamic, 'init_soil_t',                     &
3510                                init_3d%tsoil_1d(0:init_3d%nzs-1) )
3511
3512!
3513!--       level-of-detail 2 - read 3D initialization data
3514          ELSEIF ( init_3d%lod_tsoil == 2 )  THEN
3515             ALLOCATE ( init_3d%tsoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr) )
3516             
3517             CALL get_variable( id_dynamic, 'init_soil_t',                     &   
3518                             init_3d%tsoil_3d(0:init_3d%nzs-1,nys:nyn,nxl:nxr),&
3519                             nxl, nxr, nys, nyn, 0, init_3d%nzs-1 )
3520          ENDIF
3521          init_3d%from_file_tsoil = .TRUE.
3522       ENDIF
3523!
3524!--    Close input file
3525       CALL close_input_file( id_dynamic )
3526#endif
3527!
3528!--    End of CPU measurement
3529       CALL cpu_log( log_point_s(85), 'NetCDF input init', 'stop' )
3530
3531    END SUBROUTINE netcdf_data_input_init_lsm   
3532
3533!------------------------------------------------------------------------------!
3534! Description:
3535! ------------
3536!> Reads data at lateral and top boundaries derived from larger-scale model
3537!> (COSMO) by Inifor.
3538!------------------------------------------------------------------------------!
3539    SUBROUTINE netcdf_data_input_offline_nesting
3540
3541       USE control_parameters,                                                 &
3542           ONLY:  air_chemistry, bc_dirichlet_l, bc_dirichlet_n,               &
3543                  bc_dirichlet_r, bc_dirichlet_s, humidity, neutral,           &
3544                  nesting_offline, time_since_reference_point
3545
3546       USE indices,                                                            &
3547           ONLY:  nxl, nxlu, nxr, nyn, nys, nysv, nzb, nzt
3548
3549       IMPLICIT NONE
3550       
3551       INTEGER(iwp) ::  id_dynamic !< NetCDF id of dynamic input file
3552       INTEGER(iwp) ::  n          !< running index for chemistry variables
3553       INTEGER(iwp) ::  num_vars   !< number of variables in netcdf input file
3554       INTEGER(iwp) ::  t          !< running index time dimension
3555!
3556!--    Skip input if no forcing from larger-scale models is applied.
3557       IF ( .NOT. nesting_offline )  RETURN
3558
3559!
3560!--    CPU measurement
3561       CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'start' )
3562
3563#if defined ( __netcdf )
3564!
3565!--    Open file in read-only mode
3566       CALL open_read_file( TRIM( input_file_dynamic ) //                      &
3567                            TRIM( coupling_char ), id_dynamic )
3568!
3569!--    Initialize INIFOR forcing.
3570       IF ( .NOT. nest_offl%init )  THEN
3571!
3572!--       At first, inquire all variable names.
3573          CALL inquire_num_variables( id_dynamic, num_vars )
3574!
3575!--       Allocate memory to store variable names.
3576          ALLOCATE( nest_offl%var_names(1:num_vars) )
3577          CALL inquire_variable_names( id_dynamic, nest_offl%var_names )
3578!
3579!--       Read time dimension, allocate memory and finally read time array
3580          CALL netcdf_data_input_get_dimension_length( id_dynamic,             &
3581                                                       nest_offl%nt, 'time' )
3582
3583          IF ( check_existence( nest_offl%var_names, 'time' ) )  THEN
3584             ALLOCATE( nest_offl%time(0:nest_offl%nt-1) )
3585             CALL get_variable( id_dynamic, 'time', nest_offl%time )
3586          ENDIF
3587!
3588!--       Read vertical dimension of scalar und w grid
3589          CALL netcdf_data_input_get_dimension_length( id_dynamic,             &
3590                                                       nest_offl%nzu, 'z' )
3591          CALL netcdf_data_input_get_dimension_length( id_dynamic,             &
3592                                                       nest_offl%nzw, 'zw' )
3593
3594          IF ( check_existence( nest_offl%var_names, 'z' ) )  THEN
3595             ALLOCATE( nest_offl%zu_atmos(1:nest_offl%nzu) )
3596             CALL get_variable( id_dynamic, 'z', nest_offl%zu_atmos )
3597          ENDIF
3598          IF ( check_existence( nest_offl%var_names, 'zw' ) )  THEN
3599             ALLOCATE( nest_offl%zw_atmos(1:nest_offl%nzw) )
3600             CALL get_variable( id_dynamic, 'zw', nest_offl%zw_atmos )
3601          ENDIF
3602
3603!
3604!--       Read surface pressure
3605          IF ( check_existence( nest_offl%var_names,                           &
3606                                'surface_forcing_surface_pressure' ) )  THEN
3607             ALLOCATE( nest_offl%surface_pressure(0:nest_offl%nt-1) )
3608             CALL get_variable( id_dynamic,                                    &
3609                                'surface_forcing_surface_pressure',            &
3610                                nest_offl%surface_pressure )
3611          ENDIF
3612!
3613!--       Set control flag to indicate that initialization is already done
3614          nest_offl%init = .TRUE.
3615
3616       ENDIF
3617
3618!
3619!--    Obtain time index for current input starting at 0.
3620!--    @todo: At the moment INIFOR and simulated time correspond
3621!--           to each other. If required, adjust to daytime.
3622       nest_offl%tind = MINLOC( ABS( nest_offl%time -                          &
3623                                     time_since_reference_point ), DIM = 1 )   &
3624                        - 1
3625       nest_offl%tind_p = nest_offl%tind + 1       
3626!
3627!--    Read geostrophic wind components
3628       DO  t = nest_offl%tind, nest_offl%tind_p
3629          CALL get_variable_pr( id_dynamic, 'ls_forcing_ug', t+1,              &
3630                                nest_offl%ug(t-nest_offl%tind,nzb+1:nzt) )
3631          CALL get_variable_pr( id_dynamic, 'ls_forcing_vg', t+1,              &
3632                                nest_offl%vg(t-nest_offl%tind,nzb+1:nzt) )
3633       ENDDO
3634!
3635!--    Read data at lateral and top boundaries. Please note, at left and
3636!--    right domain boundary, yz-layers are read for u, v, w, pt and q.
3637!--    For the v-component, the data starts at nysv, while for the other
3638!--    quantities the data starts at nys. This is equivalent at the north
3639!--    and south domain boundary for the u-component.
3640!--    Note, lateral data is also accessed by parallel IO, which is the reason
3641!--    why different arguments are passed depending on the boundary control
3642!--    flags. Cores that do not belong to the respective boundary just make
3643!--    a dummy read with count = 0, just in order to participate the collective
3644!--    operation.
3645!--    Read data for western boundary   
3646       CALL get_variable( id_dynamic, 'ls_forcing_left_u',                     &
3647                          nest_offl%u_left,                                    & ! array to be read
3648                          MERGE( nys+1, 1, bc_dirichlet_l),                    & ! start index y direction
3649                          MERGE( nzb+1, 1, bc_dirichlet_l),                    & ! start index z direction
3650                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         & ! start index time dimension
3651                          MERGE( nyn-nys+1, 0, bc_dirichlet_l),                & ! number of elements along y
3652                          MERGE( nest_offl%nzu, 0, bc_dirichlet_l),            & ! number of elements alogn z
3653                          MERGE( 2, 0, bc_dirichlet_l),                        & ! number of time steps (2 or 0)
3654                          .TRUE. )                                               ! parallel IO when compiled accordingly
3655     
3656       CALL get_variable( id_dynamic, 'ls_forcing_left_v',                     &
3657                          nest_offl%v_left,                                    &
3658                          MERGE( nysv, 1, bc_dirichlet_l),                     &
3659                          MERGE( nzb+1, 1, bc_dirichlet_l),                    &
3660                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         &
3661                          MERGE( nyn-nysv+1, 0, bc_dirichlet_l),               &
3662                          MERGE( nest_offl%nzu, 0, bc_dirichlet_l),            &
3663                          MERGE( 2, 0, bc_dirichlet_l),                        &
3664                          .TRUE. )                                       
3665
3666       CALL get_variable( id_dynamic, 'ls_forcing_left_w',                     &
3667                          nest_offl%w_left,                                    &
3668                          MERGE( nys+1, 1, bc_dirichlet_l),                    &
3669                          MERGE( nzb+1, 1, bc_dirichlet_l),                    &
3670                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),         &
3671                          MERGE( nyn-nys+1, 0, bc_dirichlet_l),                &
3672                          MERGE( nest_offl%nzw, 0, bc_dirichlet_l),            &
3673                          MERGE( 2, 0, bc_dirichlet_l),                        &
3674                          .TRUE. )   
3675
3676       IF ( .NOT. neutral )  THEN
3677          CALL get_variable( id_dynamic, 'ls_forcing_left_pt',                 &
3678                             nest_offl%pt_left,                                &
3679                             MERGE( nys+1, 1, bc_dirichlet_l),                 &
3680                             MERGE( nzb+1, 1, bc_dirichlet_l),                 &
3681                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),      &
3682                             MERGE( nyn-nys+1, 0, bc_dirichlet_l),             &
3683                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),         &
3684                             MERGE( 2, 0, bc_dirichlet_l),                     &
3685                             .TRUE. )
3686       ENDIF
3687
3688       IF ( humidity )  THEN
3689          CALL get_variable( id_dynamic, 'ls_forcing_left_qv',                 &
3690                             nest_offl%q_left,                                 &
3691                             MERGE( nys+1, 1, bc_dirichlet_l),                 &
3692                             MERGE( nzb+1, 1, bc_dirichlet_l),                 &
3693                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),      &
3694                             MERGE( nyn-nys+1, 0, bc_dirichlet_l),             &
3695                             MERGE( nest_offl%nzu, 0, bc_dirichlet_l),         &
3696                             MERGE( 2, 0, bc_dirichlet_l),                     &
3697                             .TRUE. )
3698       ENDIF
3699       
3700       IF ( air_chemistry )  THEN
3701          DO  n = 1, UBOUND(nest_offl%var_names_chem_l, 1)
3702             IF ( check_existence( nest_offl%var_names,                        &
3703                                   nest_offl%var_names_chem_l(n) ) )  THEN 
3704                CALL get_variable( id_dynamic,                                 &
3705                           TRIM( nest_offl%var_names_chem_l(n) ),              &
3706                           nest_offl%chem_left(:,:,:,n),                       &
3707                           MERGE( nys+1, 1, bc_dirichlet_l),                   &
3708                           MERGE( nzb+1, 1, bc_dirichlet_l),                   &
3709                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_l),        &
3710                           MERGE( nyn-nys+1, 0, bc_dirichlet_l),               &
3711                           MERGE( nest_offl%nzu, 0, bc_dirichlet_l),           &
3712                           MERGE( 2, 0, bc_dirichlet_l),                       &
3713                           .TRUE. )
3714                nest_offl%chem_from_file_l(n) = .TRUE.
3715             ENDIF
3716          ENDDO
3717       ENDIF
3718!
3719!--    Read data for eastern boundary   
3720       CALL get_variable( id_dynamic, 'ls_forcing_right_u',                    &
3721                          nest_offl%u_right,                                   &
3722                          MERGE( nys+1, 1, bc_dirichlet_r),                    &
3723                          MERGE( nzb+1, 1, bc_dirichlet_r),                    &
3724                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
3725                          MERGE( nyn-nys+1, 0, bc_dirichlet_r),                &
3726                          MERGE( nest_offl%nzu, 0, bc_dirichlet_r),            &
3727                          MERGE( 2, 0, bc_dirichlet_r),                        &
3728                          .TRUE. )                                             
3729     
3730       CALL get_variable( id_dynamic, 'ls_forcing_right_v',                    &
3731                          nest_offl%v_right,                                   &
3732                          MERGE( nysv, 1, bc_dirichlet_r),                     &
3733                          MERGE( nzb+1, 1, bc_dirichlet_r),                    &
3734                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
3735                          MERGE( nyn-nysv+1, 0, bc_dirichlet_r),               &
3736                          MERGE( nest_offl%nzu, 0, bc_dirichlet_r),            &
3737                          MERGE( 2, 0, bc_dirichlet_r),                        &
3738                          .TRUE. )                                             
3739
3740       CALL get_variable( id_dynamic, 'ls_forcing_right_w',                    &
3741                          nest_offl%w_right,                                   &
3742                          MERGE( nys+1, 1, bc_dirichlet_r),                    &
3743                          MERGE( nzb+1, 1, bc_dirichlet_r),                    &
3744                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),         &
3745                          MERGE( nyn-nys+1, 0, bc_dirichlet_r),                &
3746                          MERGE( nest_offl%nzw, 0, bc_dirichlet_r),            &
3747                          MERGE( 2, 0, bc_dirichlet_r),                        &
3748                          .TRUE. )   
3749
3750       IF ( .NOT. neutral )  THEN
3751          CALL get_variable( id_dynamic, 'ls_forcing_right_pt',                &
3752                             nest_offl%pt_right,                               &
3753                             MERGE( nys+1, 1, bc_dirichlet_r),                 &
3754                             MERGE( nzb+1, 1, bc_dirichlet_r),                 &
3755                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),      &
3756                             MERGE( nyn-nys+1, 0, bc_dirichlet_r),             &
3757                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),         &
3758                             MERGE( 2, 0, bc_dirichlet_r),                     &
3759                             .TRUE. )
3760       ENDIF
3761
3762       IF ( humidity )  THEN
3763          CALL get_variable( id_dynamic, 'ls_forcing_right_qv',                &
3764                             nest_offl%q_right,                                &
3765                             MERGE( nys+1, 1, bc_dirichlet_r),                 &
3766                             MERGE( nzb+1, 1, bc_dirichlet_r),                 &
3767                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),      &
3768                             MERGE( nyn-nys+1, 0, bc_dirichlet_r),             &
3769                             MERGE( nest_offl%nzu, 0, bc_dirichlet_r),         &
3770                             MERGE( 2, 0, bc_dirichlet_r),                     &
3771                             .TRUE. )
3772       ENDIF
3773       
3774       IF ( air_chemistry )  THEN
3775          DO  n = 1, UBOUND(nest_offl%var_names_chem_r, 1)
3776             IF ( check_existence( nest_offl%var_names,                        &
3777                                   nest_offl%var_names_chem_r(n) ) )  THEN     
3778                CALL get_variable( id_dynamic,                                 &
3779                           TRIM( nest_offl%var_names_chem_r(n) ),              &
3780                           nest_offl%chem_right(:,:,:,n),                      &
3781                           MERGE( nys+1, 1, bc_dirichlet_r),                   &
3782                           MERGE( nzb+1, 1, bc_dirichlet_r),                   &
3783                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_r),        &
3784                           MERGE( nyn-nys+1, 0, bc_dirichlet_r),               &
3785                           MERGE( nest_offl%nzu, 0, bc_dirichlet_r),           &
3786                           MERGE( 2, 0, bc_dirichlet_r),                       &
3787                           .TRUE. )
3788                nest_offl%chem_from_file_r(n) = .TRUE.
3789             ENDIF
3790          ENDDO
3791       ENDIF
3792!
3793!--    Read data for northern boundary
3794       CALL get_variable( id_dynamic, 'ls_forcing_north_u',                    & ! array to be read
3795                          nest_offl%u_north,                                   & ! start index x direction
3796                          MERGE( nxlu, 1, bc_dirichlet_n ),                    & ! start index z direction
3797                          MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
3798                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
3799                          MERGE( nxr-nxlu+1, 0, bc_dirichlet_n ),              & ! number of elements alogn z
3800                          MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
3801                          MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
3802                          .TRUE. )                                             
3803                                                                               
3804       CALL get_variable( id_dynamic, 'ls_forcing_north_v',                    & ! array to be read
3805                          nest_offl%v_north,                                   & ! start index x direction
3806                          MERGE( nxl+1, 1, bc_dirichlet_n ),                   & ! start index z direction
3807                          MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
3808                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
3809                          MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),               & ! number of elements alogn z
3810                          MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
3811                          MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
3812                          .TRUE. )                                             
3813                                                                               
3814       CALL get_variable( id_dynamic, 'ls_forcing_north_w',                    & ! array to be read
3815                          nest_offl%w_north,                                   & ! start index x direction
3816                          MERGE( nxl+1, 1, bc_dirichlet_n ),                   & ! start index z direction
3817                          MERGE( nzb+1, 1, bc_dirichlet_n ),                   & ! start index time dimension
3818                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),        & ! number of elements along x
3819                          MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),               & ! number of elements alogn z
3820                          MERGE( nest_offl%nzw, 0, bc_dirichlet_n ),           & ! number of time steps (2 or 0)
3821                          MERGE( 2, 0, bc_dirichlet_n ),                       & ! parallel IO when compiled accordingly
3822                          .TRUE. )                                             
3823                                                                               
3824       IF ( .NOT. neutral )  THEN                                             
3825          CALL get_variable( id_dynamic, 'ls_forcing_north_pt',                & ! array to be read
3826                             nest_offl%pt_north,                               & ! start index x direction
3827                             MERGE( nxl+1, 1, bc_dirichlet_n ),                & ! start index z direction
3828                             MERGE( nzb+1, 1, bc_dirichlet_n ),                & ! start index time dimension
3829                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),     & ! number of elements along x
3830                             MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),            & ! number of elements alogn z
3831                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
3832                             MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
3833                             .TRUE. )                                             
3834       ENDIF                                                                   
3835       IF ( humidity )  THEN                                                   
3836          CALL get_variable( id_dynamic, 'ls_forcing_north_qv',                & ! array to be read
3837                             nest_offl%q_north,                                & ! start index x direction
3838                             MERGE( nxl+1, 1, bc_dirichlet_n ),                & ! start index z direction
3839                             MERGE( nzb+1, 1, bc_dirichlet_n ),                & ! start index time dimension
3840                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),     & ! number of elements along x
3841                             MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),            & ! number of elements alogn z
3842                             MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),        & ! number of time steps (2 or 0)
3843                             MERGE( 2, 0, bc_dirichlet_n ),                    & ! parallel IO when compiled accordingly
3844                             .TRUE. )                                             
3845       ENDIF                                                                   
3846                                                                               
3847       IF ( air_chemistry )  THEN                                             
3848          DO  n = 1, UBOUND(nest_offl%var_names_chem_n, 1)                     
3849             IF ( check_existence( nest_offl%var_names,                        &
3850                                   nest_offl%var_names_chem_n(n) ) )  THEN     
3851                CALL get_variable( id_dynamic,                                 &
3852                           TRIM( nest_offl%var_names_chem_n(n) ),              &
3853                           nest_offl%chem_north(:,:,:,n),                      &
3854                           MERGE( nxl+1, 1, bc_dirichlet_n ),                  &
3855                           MERGE( nzb+1, 1, bc_dirichlet_n ),                  &
3856                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_n ),       &
3857                           MERGE( nxr-nxl+1, 0, bc_dirichlet_n ),              &
3858                           MERGE( nest_offl%nzu, 0, bc_dirichlet_n ),          &
3859                           MERGE( 2, 0, bc_dirichlet_n ),                      &
3860                           .TRUE. )
3861                nest_offl%chem_from_file_n(n) = .TRUE.
3862             ENDIF
3863          ENDDO
3864       ENDIF
3865!
3866!--    Read data for southern boundary
3867       CALL get_variable( id_dynamic, 'ls_forcing_south_u',                    & ! array to be read
3868                          nest_offl%u_south,                                   & ! start index x direction
3869                          MERGE( nxlu, 1, bc_dirichlet_s ),                    & ! start index z direction
3870                          MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
3871                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
3872                          MERGE( nxr-nxlu+1, 0, bc_dirichlet_s ),              & ! number of elements alogn z
3873                          MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
3874                          MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
3875                          .TRUE. )                                             
3876                                                                               
3877       CALL get_variable( id_dynamic, 'ls_forcing_south_v',                    & ! array to be read
3878                          nest_offl%v_south,                                   & ! start index x direction
3879                          MERGE( nxl+1, 1, bc_dirichlet_s ),                   & ! start index z direction
3880                          MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
3881                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
3882                          MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),               & ! number of elements alogn z
3883                          MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
3884                          MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
3885                          .TRUE. )                                             
3886                                                                               
3887       CALL get_variable( id_dynamic, 'ls_forcing_south_w',                    & ! array to be read
3888                          nest_offl%w_south,                                   & ! start index x direction
3889                          MERGE( nxl+1, 1, bc_dirichlet_s ),                   & ! start index z direction
3890                          MERGE( nzb+1, 1, bc_dirichlet_s ),                   & ! start index time dimension
3891                          MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),        & ! number of elements along x
3892                          MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),               & ! number of elements alogn z
3893                          MERGE( nest_offl%nzw, 0, bc_dirichlet_s ),           & ! number of time steps (2 or 0)
3894                          MERGE( 2, 0, bc_dirichlet_s ),                       & ! parallel IO when compiled accordingly
3895                          .TRUE. )                                             
3896                                                                               
3897       IF ( .NOT. neutral )  THEN                                             
3898          CALL get_variable( id_dynamic, 'ls_forcing_south_pt',                & ! array to be read
3899                             nest_offl%pt_south,                               & ! start index x direction
3900                             MERGE( nxl+1, 1, bc_dirichlet_s ),                & ! start index z direction
3901                             MERGE( nzb+1, 1, bc_dirichlet_s ),                & ! start index time dimension
3902                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),     & ! number of elements along x
3903                             MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),            & ! number of elements alogn z
3904                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
3905                             MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
3906                             .TRUE. )                                             
3907       ENDIF                                                                   
3908       IF ( humidity )  THEN                                                   
3909          CALL get_variable( id_dynamic, 'ls_forcing_south_qv',                & ! array to be read
3910                             nest_offl%q_south,                                & ! start index x direction
3911                             MERGE( nxl+1, 1, bc_dirichlet_s ),                & ! start index z direction
3912                             MERGE( nzb+1, 1, bc_dirichlet_s ),                & ! start index time dimension
3913                             MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),     & ! number of elements along x
3914                             MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),            & ! number of elements alogn z
3915                             MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),        & ! number of time steps (2 or 0)
3916                             MERGE( 2, 0, bc_dirichlet_s ),                    & ! parallel IO when compiled accordingly
3917                             .TRUE. )                                             
3918       ENDIF                                                                   
3919                                                                               
3920       IF ( air_chemistry )  THEN                                             
3921          DO  n = 1, UBOUND(nest_offl%var_names_chem_s, 1)                     
3922             IF ( check_existence( nest_offl%var_names,                        &
3923                                   nest_offl%var_names_chem_s(n) ) )  THEN     
3924                CALL get_variable( id_dynamic,                                 &
3925                           TRIM( nest_offl%var_names_chem_s(n) ),              &
3926                           nest_offl%chem_south(:,:,:,n),                      &
3927                           MERGE( nxl+1, 1, bc_dirichlet_s ),                  &
3928                           MERGE( nzb+1, 1, bc_dirichlet_s ),                  &
3929                           MERGE( nest_offl%tind+1, 1, bc_dirichlet_s ),       &
3930                           MERGE( nxr-nxl+1, 0, bc_dirichlet_s ),              &
3931                           MERGE( nest_offl%nzu, 0, bc_dirichlet_s ),          &
3932                           MERGE( 2, 0, bc_dirichlet_s ),                      &
3933                           .TRUE. )
3934                nest_offl%chem_from_file_s(n) = .TRUE.
3935             ENDIF
3936          ENDDO
3937       ENDIF
3938!
3939!--    Top boundary
3940       CALL get_variable( id_dynamic, 'ls_forcing_top_u',                      &
3941                             nest_offl%u_top(0:1,nys:nyn,nxlu:nxr),            &
3942                             nxlu, nys+1, nest_offl%tind+1,                    &
3943                             nxr-nxlu+1, nyn-nys+1, 2, .TRUE. )
3944
3945       CALL get_variable( id_dynamic, 'ls_forcing_top_v',                      &
3946                             nest_offl%v_top(0:1,nysv:nyn,nxl:nxr),            &
3947                             nxl+1, nysv, nest_offl%tind+1,                    &
3948                             nxr-nxl+1, nyn-nysv+1, 2, .TRUE. )
3949                             
3950       CALL get_variable( id_dynamic, 'ls_forcing_top_w',                      &
3951                             nest_offl%w_top(0:1,nys:nyn,nxl:nxr),             &
3952                             nxl+1, nys+1, nest_offl%tind+1,                   &
3953                             nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
3954                             
3955       IF ( .NOT. neutral )  THEN
3956          CALL get_variable( id_dynamic, 'ls_forcing_top_pt',                  &
3957                                nest_offl%pt_top(0:1,nys:nyn,nxl:nxr),         &
3958                                nxl+1, nys+1, nest_offl%tind+1,                &
3959                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
3960       ENDIF
3961       IF ( humidity )  THEN
3962          CALL get_variable( id_dynamic, 'ls_forcing_top_qv',                  &
3963                                nest_offl%q_top(0:1,nys:nyn,nxl:nxr),          &
3964                                nxl+1, nys+1, nest_offl%tind+1,                &
3965                                nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
3966       ENDIF
3967       
3968       IF ( air_chemistry )  THEN
3969          DO  n = 1, UBOUND(nest_offl%var_names_chem_t, 1)
3970             IF ( check_existence( nest_offl%var_names,                     &
3971                                   nest_offl%var_names_chem_t(n) ) )  THEN     
3972                CALL get_variable( id_dynamic,                                 &
3973                              TRIM( nest_offl%var_names_chem_t(n) ),           &
3974                              nest_offl%chem_top(0:1,nys:nyn,nxl:nxr,n),       &
3975                              nxl+1, nys+1, nest_offl%tind+1,                  &
3976                              nxr-nxl+1, nyn-nys+1, 2, .TRUE. )
3977                nest_offl%chem_from_file_t(n) = .TRUE.
3978             ENDIF
3979          ENDDO
3980       ENDIF
3981
3982!
3983!--    Close input file
3984       CALL close_input_file( id_dynamic )
3985#endif
3986!
3987!--    End of CPU measurement
3988       CALL cpu_log( log_point_s(86), 'NetCDF input forcing', 'stop' )
3989
3990    END SUBROUTINE netcdf_data_input_offline_nesting
3991
3992
3993!------------------------------------------------------------------------------!
3994! Description:
3995! ------------
3996!> Checks input file for consistency and minimum requirements.
3997!------------------------------------------------------------------------------!
3998    SUBROUTINE netcdf_data_input_check_dynamic
3999
4000       USE control_parameters,                                                 &
4001           ONLY:  initializing_actions, message_string, nesting_offline 
4002
4003       IMPLICIT NONE
4004
4005!
4006!--    In case of forcing, check whether dynamic input file is present
4007       IF ( .NOT. input_pids_dynamic  .AND.  nesting_offline  )  THEN
4008          message_string = 'nesting_offline = .TRUE. requires dynamic '  //    &
4009                            'input file ' //                                   &
4010                            TRIM( input_file_dynamic ) // TRIM( coupling_char )
4011          CALL message( 'netcdf_data_input_mod', 'PA0546', 1, 2, 0, 6, 0 )
4012       ENDIF
4013!
4014!--    Dynamic input file must also be present if initialization via inifor is
4015!--    prescribed.
4016       IF ( .NOT. input_pids_dynamic  .AND.                                    &
4017            INDEX( initializing_actions, 'inifor' ) /= 0 )  THEN
4018          message_string = 'initializing_actions = inifor requires dynamic ' //&
4019                           'input file ' // TRIM( input_file_dynamic ) //      &
4020                           TRIM( coupling_char )
4021          CALL message( 'netcdf_data_input_mod', 'PA0547', 1, 2, 0, 6, 0 )
4022       ENDIF
4023
4024    END SUBROUTINE netcdf_data_input_check_dynamic
4025
4026!------------------------------------------------------------------------------!
4027! Description:
4028! ------------
4029!> Checks input file for consistency and minimum requirements.
4030!------------------------------------------------------------------------------!
4031    SUBROUTINE netcdf_data_input_check_static
4032
4033       USE arrays_3d,                                                          &
4034           ONLY:  zu
4035
4036       USE control_parameters,                                                 &
4037           ONLY:  land_surface, message_string, urban_surface
4038
4039       USE indices,                                                            &
4040           ONLY:  nxl, nxr, nyn, nys, wall_flags_0
4041
4042       IMPLICIT NONE
4043
4044       INTEGER(iwp) ::  i      !< loop index along x-direction
4045       INTEGER(iwp) ::  j      !< loop index along y-direction
4046       INTEGER(iwp) ::  n_surf !< number of different surface types at given location
4047
4048       LOGICAL      ::  check_passed !< flag indicating if a check passed
4049
4050!
4051!--    Return if no static input file is available
4052       IF ( .NOT. input_pids_static )  RETURN
4053!
4054!--    Check for correct dimension of surface_fractions, should run from 0-2.
4055       IF ( surface_fraction_f%from_file )  THEN
4056          IF ( surface_fraction_f%nf-1 > 2 )  THEN
4057             message_string = 'nsurface_fraction must not be larger than 3.' 
4058             CALL message( 'netcdf_data_input_mod', 'PA0580', 1, 2, 0, 6, 0 )
4059          ENDIF
4060       ENDIF
4061!
4062!--    Check orography for fill-values. For the moment, give an error message.
4063!--    More advanced methods, e.g. a nearest neighbor algorithm as used in GIS
4064!--    systems might be implemented later.
4065!--    Please note, if no terrain height is provided, it is set to 0.
4066       IF ( ANY( terrain_height_f%var == terrain_height_f%fill ) )  THEN
4067          message_string = 'NetCDF variable zt is not ' //                     &
4068                           'allowed to have missing data'
4069          CALL message( 'netcdf_data_input_mod', 'PA0550', 2, 2, myid, 6, 0 )
4070       ENDIF
4071!
4072!--    Check for negative terrain heights
4073       IF ( ANY( terrain_height_f%var < 0.0_wp ) )  THEN
4074          message_string = 'NetCDF variable zt is not ' //                     &
4075                           'allowed to have negative values'
4076          CALL message( 'netcdf_data_input_mod', 'PA0551', 2, 2, myid, 6, 0 )
4077       ENDIF
4078!
4079!--    If 3D buildings are read, check if building information is consistent
4080!--    to numeric grid.
4081       IF ( buildings_f%from_file )  THEN
4082          IF ( buildings_f%lod == 2 )  THEN
4083             IF ( buildings_f%nz > SIZE( zu ) )  THEN
4084                message_string = 'Reading 3D building data - too much ' //     &
4085                                 'data points along the vertical coordinate.'
4086                CALL message( 'netcdf_data_input_mod', 'PA0552', 2, 2, 0, 6, 0 )
4087             ENDIF
4088
4089             IF ( ANY( ABS( buildings_f%z(0:buildings_f%nz-1) -                &
4090                       zu(0:buildings_f%nz-1) ) > 1E-6_wp ) )  THEN
4091                message_string = 'Reading 3D building data - vertical ' //     &
4092                                 'coordinate do not match numeric grid.'
4093                CALL message( 'netcdf_data_input_mod', 'PA0553', 2, 2, myid, 6, 0 )
4094             ENDIF
4095          ENDIF
4096       ENDIF
4097
4098!
4099!--    Skip further checks concerning buildings and natural surface properties
4100!--    if no urban surface and land surface model are applied.
4101       IF (  .NOT. land_surface  .AND.  .NOT. urban_surface )  RETURN
4102!
4103!--    Check for minimum requirement of surface-classification data in case
4104!--    static input file is used.
4105       IF ( ( .NOT. vegetation_type_f%from_file  .OR.                          &
4106              .NOT. pavement_type_f%from_file    .OR.                          &
4107              .NOT. water_type_f%from_file       .OR.                          &
4108              .NOT. soil_type_f%from_file             ) .OR.                   &
4109             ( urban_surface  .AND.  .NOT. building_type_f%from_file ) )  THEN
4110          message_string = 'Minimum requirement for surface classification ' //&
4111                           'is not fulfilled. At least ' //                    &
4112                           'vegetation_type, pavement_type, ' //               &
4113                           'soil_type and water_type are '//                   &
4114                           'required. If urban-surface model is applied, ' //  &
4115                           'also building_type is required'
4116          CALL message( 'netcdf_data_input_mod', 'PA0554', 1, 2, 0, 6, 0 )
4117       ENDIF
4118!
4119!--    Check for general availability of input variables.
4120!--    If vegetation_type is 0 at any location, vegetation_pars as well as
4121!--    root_area_dens_s are required.
4122       IF ( vegetation_type_f%from_file )  THEN
4123          IF ( ANY( vegetation_type_f%var == 0 ) )  THEN
4124             IF ( .NOT. vegetation_pars_f%from_file )  THEN
4125                message_string = 'If vegetation_type = 0 at any location, ' // &
4126                                 'vegetation_pars is required'
4127                CALL message( 'netcdf_data_input_mod', 'PA0555', 2, 2, -1, 6, 0 )
4128             ENDIF
4129             IF ( .NOT. root_area_density_lsm_f%from_file )  THEN
4130                message_string = 'If vegetation_type = 0 at any location, ' // &
4131                                 'root_area_dens_s is required'
4132                CALL message( 'netcdf_data_input_mod', 'PA0556', 2, 2, myid, 6, 0 )
4133             ENDIF
4134          ENDIF
4135       ENDIF
4136!
4137!--    If soil_type is zero at any location, soil_pars is required.
4138       IF ( soil_type_f%from_file )  THEN
4139          check_passed = .TRUE.
4140          IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
4141             IF ( ANY( soil_type_f%var_2d == 0 ) )  THEN
4142                IF ( .NOT. soil_pars_f%from_file )  check_passed = .FALSE.
4143             ENDIF
4144          ELSE
4145             IF ( ANY( soil_type_f%var_3d == 0 ) )  THEN
4146                IF ( .NOT. soil_pars_f%from_file )  check_passed = .FALSE.
4147             ENDIF
4148          ENDIF
4149          IF ( .NOT. check_passed )  THEN
4150             message_string = 'If soil_type = 0 at any location, ' //          &
4151                              'soil_pars is required'
4152             CALL message( 'netcdf_data_input_mod', 'PA0557', 2, 2, myid, 6, 0 )
4153          ENDIF
4154       ENDIF
4155!
4156!--    Buildings require a type in case of urban-surface model.
4157       IF ( buildings_f%from_file  .AND.  .NOT. building_type_f%from_file  )  THEN
4158          message_string = 'If buildings are provided, also building_type ' // &
4159                           'is required'
4160          CALL message( 'netcdf_data_input_mod', 'PA0581', 2, 2, myid, 6, 0 )
4161       ENDIF
4162!
4163!--    Buildings require an ID.
4164       IF ( buildings_f%from_file  .AND.  .NOT. building_id_f%from_file  )  THEN
4165          message_string = 'If buildings are provided, also building_id ' //   &
4166                           'is required'
4167          CALL message( 'netcdf_data_input_mod', 'PA0582', 2, 2, myid, 6, 0 )
4168       ENDIF
4169!
4170!--    If building_type is zero at any location, building_pars is required.
4171       IF ( building_type_f%from_file )  THEN
4172          IF ( ANY( building_type_f%var == 0 ) )  THEN
4173             IF ( .NOT. building_pars_f%from_file )  THEN
4174                message_string = 'If building_type = 0 at any location, ' //   &
4175                                 'building_pars is required'
4176                CALL message( 'netcdf_data_input_mod', 'PA0558', 2, 2, myid, 6, 0 )
4177             ENDIF
4178          ENDIF
4179       ENDIF
4180!
4181!--    If building_type is provided, also building_id is needed (due to the
4182!--    filtering algorithm).
4183       IF ( building_type_f%from_file  .AND.  .NOT. building_id_f%from_file )  &
4184       THEN
4185          message_string = 'If building_type is provided, also building_id '// &
4186                           'is required'
4187          CALL message( 'netcdf_data_input_mod', 'PA0519', 2, 2, myid, 6, 0 )
4188       ENDIF       
4189!
4190!--    If albedo_type is zero at any location, albedo_pars is required.
4191       IF ( albedo_type_f%from_file )  THEN
4192          IF ( ANY( albedo_type_f%var == 0 ) )  THEN
4193             IF ( .NOT. albedo_pars_f%from_file )  THEN
4194                message_string = 'If albedo_type = 0 at any location, ' //     &
4195                                 'albedo_pars is required'
4196                CALL message( 'netcdf_data_input_mod', 'PA0559', 2, 2, myid, 6, 0 )
4197             ENDIF
4198          ENDIF
4199       ENDIF
4200!
4201!--    If pavement_type is zero at any location, pavement_pars is required.
4202       IF ( pavement_type_f%from_file )  THEN
4203          IF ( ANY( pavement_type_f%var == 0 ) )  THEN
4204             IF ( .NOT. pavement_pars_f%from_file )  THEN
4205                message_string = 'If pavement_type = 0 at any location, ' //   &
4206                                 'pavement_pars is required'
4207                CALL message( 'netcdf_data_input_mod', 'PA0560', 2, 2, myid, 6, 0 )
4208             ENDIF
4209          ENDIF
4210       ENDIF
4211!
4212!--    If pavement_type is zero at any location, also pavement_subsurface_pars
4213!--    is required.
4214       IF ( pavement_type_f%from_file )  THEN
4215          IF ( ANY( pavement_type_f%var == 0 ) )  THEN
4216             IF ( .NOT. pavement_subsurface_pars_f%from_file )  THEN
4217                message_string = 'If pavement_type = 0 at any location, ' //   &
4218                                 'pavement_subsurface_pars is required'
4219                CALL message( 'netcdf_data_input_mod', 'PA0561', 2, 2, myid, 6, 0 )
4220             ENDIF
4221          ENDIF
4222       ENDIF
4223!
4224!--    If water_type is zero at any location, water_pars is required.
4225       IF ( water_type_f%from_file )  THEN
4226          IF ( ANY( water_type_f%var == 0 ) )  THEN
4227             IF ( .NOT. water_pars_f%from_file )  THEN
4228                message_string = 'If water_type = 0 at any location, ' //      &
4229                                 'water_pars is required'
4230                CALL message( 'netcdf_data_input_mod', 'PA0562', 2, 2,myid, 6, 0 )
4231             ENDIF
4232          ENDIF
4233       ENDIF
4234!
4235!--    Check for local consistency of the input data.
4236       DO  i = nxl, nxr
4237          DO  j = nys, nyn
4238!
4239!--          For each (y,x)-location at least one of the parameters
4240!--          vegetation_type, pavement_type, building_type, or water_type
4241!--          must be set to a non­missing value.
4242             IF ( land_surface  .AND.  .NOT. urban_surface )  THEN
4243                IF ( vegetation_type_f%var(j,i) == vegetation_type_f%fill  .AND.&
4244                     pavement_type_f%var(j,i)   == pavement_type_f%fill    .AND.&
4245                     water_type_f%var(j,i)      == water_type_f%fill )  THEN
4246                   WRITE( message_string, * )                                  &
4247                                    'At least one of the parameters '//        &
4248                                    'vegetation_type, pavement_type, '     //  &
4249                                    'or water_type must be set '//             &
4250                                    'to a non-missing value. Grid point: ', j, i
4251                   CALL message( 'netcdf_data_input_mod', 'PA0563', 2, 2, myid, 6, 0 )
4252                ENDIF
4253             ELSEIF ( land_surface  .AND.  urban_surface )  THEN
4254                IF ( vegetation_type_f%var(j,i) == vegetation_type_f%fill  .AND.&
4255                     pavement_type_f%var(j,i)   == pavement_type_f%fill    .AND.&
4256                     building_type_f%var(j,i)   == building_type_f%fill    .AND.&
4257                     water_type_f%var(j,i)      == water_type_f%fill )  THEN
4258                   WRITE( message_string, * )                                  &
4259                                 'At least one of the parameters '//           &
4260                                 'vegetation_type, pavement_type, '  //        &
4261                                 'building_type, or water_type must be set '// &
4262                                 'to a non-missing value. Grid point: ', j, i
4263                   CALL message( 'netcdf_data_input_mod', 'PA0563', 2, 2, myid, 6, 0 )
4264                ENDIF
4265             ENDIF
4266               
4267!
4268!--          Note that a soil_type is required for each location (y,x) where
4269!--          either vegetation_type or pavement_type is a non­missing value.
4270             IF ( ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill  .OR. &
4271                    pavement_type_f%var(j,i)   /= pavement_type_f%fill ) )  THEN
4272                check_passed = .TRUE.
4273                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
4274                   IF ( soil_type_f%var_2d(j,i) == soil_type_f%fill )          &
4275                      check_passed = .FALSE.
4276                ELSE
4277                   IF ( ANY( soil_type_f%var_3d(:,j,i) == soil_type_f%fill) )  &
4278                      check_passed = .FALSE.
4279                ENDIF
4280
4281                IF ( .NOT. check_passed )  THEN
4282                   message_string = 'soil_type is required for each '//        &
4283                                 'location (y,x) where vegetation_type or ' // &
4284                                 'pavement_type is a non-missing value.'
4285                   CALL message( 'netcdf_data_input_mod', 'PA0564',            &
4286                                  2, 2, myid, 6, 0 )
4287                ENDIF
4288             ENDIF
4289!
4290!--          Check for consistency of surface fraction. If more than one type
4291!--          is set, surface fraction need to be given and the sum must not
4292!--          be larger than 1.
4293             n_surf = 0
4294             IF ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill )       &
4295                n_surf = n_surf + 1
4296             IF ( water_type_f%var(j,i)      /= water_type_f%fill )            &
4297                n_surf = n_surf + 1
4298             IF ( pavement_type_f%var(j,i)   /= pavement_type_f%fill )         &
4299                n_surf = n_surf + 1
4300
4301             IF ( n_surf > 1 )  THEN
4302                IF ( .NOT. surface_fraction_f%from_file )  THEN
4303                   message_string = 'If more than one surface type is ' //     &
4304                                 'given at a location, surface_fraction ' //   &
4305                                 'must be provided.'
4306                   CALL message( 'netcdf_data_input_mod', 'PA0565',            &
4307                                  2, 2, myid, 6, 0 )
4308                ELSEIF ( ANY ( surface_fraction_f%frac(:,j,i) ==               &
4309                               surface_fraction_f%fill ) )  THEN
4310                   message_string = 'If more than one surface type is ' //     &
4311                                 'given at a location, surface_fraction ' //   &
4312                                 'must be provided.'
4313                   CALL message( 'netcdf_data_input_mod', 'PA0565',            &
4314                                  2, 2, myid, 6, 0 )
4315                ENDIF
4316             ENDIF
4317!
4318!--          Check for further mismatches. e.g. relative fractions exceed 1 or
4319!--          vegetation_type is set but surface vegetation fraction is zero,
4320!--          etc..
4321             IF ( surface_fraction_f%from_file )  THEN
4322!
4323!--             Sum of relative fractions must not exceed 1.
4324                IF ( SUM ( surface_fraction_f%frac(0:2,j,i) ) > 1.0_wp )  THEN
4325                   message_string = 'surface_fraction must not exceed 1'
4326                   CALL message( 'netcdf_data_input_mod', 'PA0566',            &
4327                                  2, 2, myid, 6, 0 )
4328                ENDIF
4329!
4330!--             Relative fraction for a type must not be zero at locations where
4331!--             this type is set.
4332                IF (                                                           &
4333                  ( vegetation_type_f%var(j,i) /= vegetation_type_f%fill  .AND.&
4334                 ( surface_fraction_f%frac(ind_veg_wall,j,i) == 0.0_wp .OR.    &
4335                   surface_fraction_f%frac(ind_veg_wall,j,i) ==                &
4336                                                     surface_fraction_f%fill ) &
4337                  )  .OR.                                                      &
4338                  ( pavement_type_f%var(j,i) /= pavement_type_f%fill     .AND. &
4339                 ( surface_fraction_f%frac(ind_pav_green,j,i) == 0.0_wp .OR.   &
4340                   surface_fraction_f%frac(ind_pav_green,j,i) ==               &
4341                                                     surface_fraction_f%fill ) &
4342                  )  .OR.                                                      &
4343                  ( water_type_f%var(j,i) /= water_type_f%fill           .AND. &
4344                 ( surface_fraction_f%frac(ind_wat_win,j,i) == 0.0_wp .OR.     &
4345                   surface_fraction_f%frac(ind_wat_win,j,i) ==                 &
4346                                                     surface_fraction_f%fill ) &
4347                  ) )  THEN
4348                   WRITE( message_string, * ) 'Mismatch in setting of '     // &
4349                             'surface_fraction. Vegetation-, pavement-, or '// &
4350                             'water surface is given at (i,j) = ( ', i, j,     &
4351                             ' ), but surface fraction is 0 for the given type.'
4352                   CALL message( 'netcdf_data_input_mod', 'PA0567',            &
4353                                  2, 2, myid, 6, 0 )
4354                ENDIF
4355!
4356!--             Relative fraction for a type must not contain non-zero values
4357!--             if this type is not set.
4358                IF (                                                           &
4359                  ( vegetation_type_f%var(j,i) == vegetation_type_f%fill  .AND.&
4360                 ( surface_fraction_f%frac(ind_veg_wall,j,i) /= 0.0_wp .AND.   &
4361                   surface_fraction_f%frac(ind_veg_wall,j,i) /=                &
4362                                                     surface_fraction_f%fill ) &
4363                  )  .OR.                                                      &
4364                  ( pavement_type_f%var(j,i) == pavement_type_f%fill     .AND. &
4365                 ( surface_fraction_f%frac(ind_pav_green,j,i) /= 0.0_wp .AND.  &
4366                   surface_fraction_f%frac(ind_pav_green,j,i) /=               &
4367                                                     surface_fraction_f%fill ) &
4368                  )  .OR.                                                      &
4369                  ( water_type_f%var(j,i) == water_type_f%fill           .AND. &
4370                 ( surface_fraction_f%frac(ind_wat_win,j,i) /= 0.0_wp .AND.    &
4371                   surface_fraction_f%frac(ind_wat_win,j,i) /=                 &
4372                                                     surface_fraction_f%fill ) &
4373                  ) )  THEN
4374                   WRITE( message_string, * ) 'Mismatch in setting of '     // &
4375                             'surface_fraction. Vegetation-, pavement-, or '// &
4376                             'water surface is not given at (i,j) = ( ', i, j, &
4377                             ' ), but surface fraction is not 0 for the ' //   &
4378                             'given type.'
4379                   CALL message( 'netcdf_data_input_mod', 'PA0568',            &
4380                                  2, 2, myid, 6, 0 )
4381                ENDIF
4382             ENDIF
4383!
4384!--          Check vegetation_pars. If vegetation_type is 0, all parameters
4385!--          need to be set, otherwise, single parameters set by
4386!--          vegetation_type can be overwritten.
4387             IF ( vegetation_type_f%from_file )  THEN
4388                IF ( vegetation_type_f%var(j,i) == 0 )  THEN
4389                   IF ( ANY( vegetation_pars_f%pars_xy(:,j,i) ==               &
4390                             vegetation_pars_f%fill ) )  THEN
4391                      message_string = 'If vegetation_type(y,x) = 0, all '  // &
4392                                       'parameters of vegetation_pars at '//   &
4393                                       'this location must be set.'
4394                      CALL message( 'netcdf_data_input_mod', 'PA0569',         &
4395                                     2, 2, myid, 6, 0 )
4396                   ENDIF
4397                ENDIF
4398             ENDIF
4399!
4400!--          Check root distribution. If vegetation_type is 0, all levels must
4401!--          be set.
4402             IF ( vegetation_type_f%from_file )  THEN
4403                IF ( vegetation_type_f%var(j,i) == 0 )  THEN
4404                   IF ( ANY( root_area_density_lsm_f%var(:,j,i) ==             &
4405                             root_area_density_lsm_f%fill ) )  THEN
4406                      message_string = 'If vegetation_type(y,x) = 0, all ' //  &
4407                                       'levels of root_area_dens_s ' //        &
4408                                       'must be set at this location.'
4409                      CALL message( 'netcdf_data_input_mod', 'PA0570',         &
4410                                     2, 2, myid, 6, 0 )
4411                   ENDIF
4412                ENDIF
4413             ENDIF
4414!
4415!--          Check soil parameters. If soil_type is 0, all parameters
4416!--          must be set.
4417             IF ( soil_type_f%from_file )  THEN
4418                check_passed = .TRUE.
4419                IF ( ALLOCATED( soil_type_f%var_2d ) )  THEN
4420                   IF ( soil_type_f%var_2d(j,i) == 0 )  THEN
4421                      IF ( ANY( soil_pars_f%pars_xy(:,j,i) ==                  &
4422                                soil_pars_f%fill ) )  check_passed = .FALSE.
4423                   ENDIF
4424                ELSE
4425                   IF ( ANY( soil_type_f%var_3d(:,j,i) == 0 ) )  THEN
4426                      IF ( ANY( soil_pars_f%pars_xy(:,j,i) ==                  &
4427                                soil_pars_f%fill ) )  check_passed = .FALSE.
4428                   ENDIF
4429                ENDIF
4430                IF ( .NOT. check_passed )  THEN
4431                   message_string = 'If soil_type(y,x) = 0, all levels of '  //&
4432                                    'soil_pars at this location must be set.'
4433                   CALL message( 'netcdf_data_input_mod', 'PA0571',            &
4434                                  2, 2, myid, 6, 0 )
4435                ENDIF
4436             ENDIF
4437
4438!
4439!--          Check building parameters. If building_type is 0, all parameters
4440!--          must be set.
4441             IF ( building_type_f%from_file )  THEN
4442                IF ( building_type_f%var(j,i) == 0 )  THEN
4443                   IF ( ANY( building_pars_f%pars_xy(:,j,i) ==                 &
4444                             building_pars_f%fill ) )  THEN
4445                      message_string = 'If building_type(y,x) = 0, all ' //    &
4446                                       'parameters of building_pars at this '//&
4447                                       'location must be set.'
4448                      CALL message( 'netcdf_data_input_mod', 'PA0572',         &
4449                                     2, 2, myid, 6, 0 )
4450                   ENDIF
4451                ENDIF
4452             ENDIF
4453!
4454!--          Check if building_type is set at each building and vice versa.
4455!--          Please note, buildings are already processed and filtered.
4456!--          For this reason, consistency checks are based on wall_flags_0
4457!--          rather than buildings_f (buildings are represented by bit 6 in
4458!--          wall_flags_0).
4459             IF ( building_type_f%from_file  .AND.  buildings_f%from_file )  THEN
4460                IF ( ANY( BTEST ( wall_flags_0(:,j,i), 6 ) )  .AND.            &
4461                     building_type_f%var(j,i) == building_type_f%fill  .OR.    &
4462               .NOT. ANY( BTEST ( wall_flags_0(:,j,i), 6 ) )  .AND.            &
4463                     building_type_f%var(j,i) /= building_type_f%fill )  THEN
4464                   WRITE( message_string, * ) 'Each location where a ' //      &
4465                                   'building is set requires a type ' //       &
4466                                   '( and vice versa ) in case the ' //        &
4467                                   'urban-surface model is applied. ' //       &
4468                                   'i, j = ', i, j
4469                   CALL message( 'netcdf_data_input_mod', 'PA0573',            &
4470                                  2, 2, myid, 6, 0 )
4471                ENDIF
4472             ENDIF
4473!
4474!--          Check if at each location where a building is present also an ID
4475!--          is set and vice versa.
4476             IF ( buildings_f%from_file )  THEN
4477                IF ( ANY( BTEST ( wall_flags_0(:,j,i), 6 ) )  .AND.           &
4478                     building_id_f%var(j,i) == building_id_f%fill  .OR.       &
4479               .NOT. ANY( BTEST ( wall_flags_0(:,j,i), 6 ) )  .AND.           &
4480                     building_id_f%var(j,i) /= building_id_f%fill )  THEN
4481                   WRITE( message_string, * ) 'Each location where a ' //     &
4482                                   'building is set requires an ID ' //       &
4483                                   '( and vice versa ). i, j = ', i, j
4484                   CALL message( 'netcdf_data_input_mod', 'PA0574',           &
4485                                  2, 2, myid, 6, 0 )
4486                ENDIF
4487             ENDIF
4488!
4489!--          Check if building ID is set where a bulding is defined.
4490             IF ( buildings_f%from_file )  THEN
4491                IF ( ANY( BTEST ( wall_flags_0(:,j,i), 6 ) )  .AND.           &
4492                     building_id_f%var(j,i) == building_id_f%fill )  THEN
4493                   WRITE( message_string, * ) 'Each building grid point '//   &
4494                                              'requires an ID.', i, j
4495                   CALL message( 'netcdf_data_input_mod', 'PA0575',           &
4496                                  2, 2, myid, 6, 0 )
4497                ENDIF
4498             ENDIF
4499!
4500!--          Check albedo parameters. If albedo_type is 0, all parameters
4501!--          must be set.
4502             IF ( albedo_type_f%from_file )  THEN
4503                IF ( albedo_type_f%var(j,i) == 0 )  THEN
4504                   IF ( ANY( albedo_pars_f%pars_xy(:,j,i) ==                   &
4505                             albedo_pars_f%fill ) )  THEN
4506                      message_string = 'If albedo_type(y,x) = 0, all ' //      &
4507                                       'parameters of albedo_pars at this ' // &
4508                                       'location must be set.'
4509                      CALL message( 'netcdf_data_input_mod', 'PA0576',         &
4510                                     2, 2, myid, 6, 0 )
4511                   ENDIF
4512                ENDIF
4513             ENDIF
4514
4515!
4516!--          Check pavement parameters. If pavement_type is 0, all parameters
4517!--          of pavement_pars must be set at this location.
4518             IF ( pavement_type_f%from_file )  THEN
4519                IF ( pavement_type_f%var(j,i) == 0 )  THEN
4520                   IF ( ANY( pavement_pars_f%pars_xy(:,j,i) ==                 &
4521                             pavement_pars_f%fill ) )  THEN
4522                      message_string = 'If pavement_type(y,x) = 0, all ' //    &
4523                                       'parameters of pavement_pars at this '//&
4524                                       'location must be set.'
4525                      CALL message( 'netcdf_data_input_mod', 'PA0577',         &
4526                                     2, 2, myid, 6, 0 )
4527                   ENDIF
4528                ENDIF
4529             ENDIF
4530!
4531!--          Check pavement-subsurface parameters. If pavement_type is 0,
4532!--          all parameters of pavement_subsurface_pars must be set  at this
4533!--          location.
4534             IF ( pavement_type_f%from_file )  THEN
4535                IF ( pavement_type_f%var(j,i) == 0 )  THEN
4536                   IF ( ANY( pavement_subsurface_pars_f%pars_xyz(:,:,j,i) ==   &
4537                             pavement_subsurface_pars_f%fill ) )  THEN
4538                      message_string = 'If pavement_type(y,x) = 0, all ' //    &
4539                                       'parameters of '                  //    &
4540                                       'pavement_subsurface_pars at this '//   &
4541                                       'location must be set.'
4542                      CALL message( 'netcdf_data_input_mod', 'PA0578',         &
4543                                     2, 2, myid, 6, 0 )
4544                   ENDIF
4545                ENDIF
4546             ENDIF
4547
4548!
4549!--          Check water parameters. If water_type is 0, all parameters
4550!--          must be set  at this location.
4551             IF ( water_type_f%from_file )  THEN
4552                IF ( water_type_f%var(j,i) == 0 )  THEN
4553                   IF ( ANY( water_pars_f%pars_xy(:,j,i) ==                    &
4554                             water_pars_f%fill ) )  THEN
4555                      message_string = 'If water_type(y,x) = 0, all ' //       &
4556                                       'parameters of water_pars at this ' //  &
4557                                       'location must be set.'
4558                      CALL message( 'netcdf_data_input_mod', 'PA0579',         &
4559                                     2, 2, myid, 6, 0 )
4560                   ENDIF
4561                ENDIF
4562             ENDIF
4563
4564          ENDDO
4565       ENDDO
4566
4567    END SUBROUTINE netcdf_data_input_check_static
4568
4569!------------------------------------------------------------------------------!
4570! Description:
4571! ------------
4572!> Resize 8-bit 2D Integer array: (nys:nyn,nxl:nxr) -> (nysg:nyng,nxlg:nxrg)
4573!------------------------------------------------------------------------------!
4574    SUBROUTINE resize_array_2d_int8( var, js, je, is, ie )
4575   
4576       IMPLICIT NONE
4577
4578       INTEGER(iwp) ::  je !< upper index bound along y direction
4579       INTEGER(iwp) ::  js !< lower index bound along y direction
4580       INTEGER(iwp) ::  ie !< upper index bound along x direction
4581       INTEGER(iwp) ::  is !< lower index bound along x direction
4582       
4583       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE ::  var     !< treated variable
4584       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE ::  var_tmp !< temporary copy
4585!
4586!--    Allocate temporary variable
4587       ALLOCATE( var_tmp(js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4588!
4589!--    Temporary copy of the variable
4590       var_tmp(js:je,is:ie) = var(js:je,is:ie)
4591!
4592!--    Resize the array
4593       DEALLOCATE( var )
4594       ALLOCATE( var(js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4595!
4596!--    Transfer temporary copy back to original array
4597       var(js:je,is:ie) = var_tmp(js:je,is:ie)
4598
4599    END SUBROUTINE resize_array_2d_int8
4600   
4601!------------------------------------------------------------------------------!
4602! Description:
4603! ------------
4604!> Resize 32-bit 2D Integer array: (nys:nyn,nxl:nxr) -> (nysg:nyng,nxlg:nxrg)
4605!------------------------------------------------------------------------------!
4606    SUBROUTINE resize_array_2d_int32( var, js, je, is, ie )
4607
4608       IMPLICIT NONE
4609       
4610       INTEGER(iwp) ::  je !< upper index bound along y direction
4611       INTEGER(iwp) ::  js !< lower index bound along y direction
4612       INTEGER(iwp) ::  ie !< upper index bound along x direction
4613       INTEGER(iwp) ::  is !< lower index bound along x direction
4614
4615       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  var     !< treated variable
4616       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  var_tmp !< temporary copy
4617!
4618!--    Allocate temporary variable
4619       ALLOCATE( var_tmp(js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4620!
4621!--    Temporary copy of the variable
4622       var_tmp(js:je,is:ie) = var(js:je,is:ie)
4623!
4624!--    Resize the array
4625       DEALLOCATE( var )
4626       ALLOCATE( var(js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4627!
4628!--    Transfer temporary copy back to original array
4629       var(js:je,is:ie) = var_tmp(js:je,is:ie)
4630
4631    END SUBROUTINE resize_array_2d_int32
4632   
4633!------------------------------------------------------------------------------!
4634! Description:
4635! ------------
4636!> Resize 8-bit 3D Integer array: (:,nys:nyn,nxl:nxr) -> (:,nysg:nyng,nxlg:nxrg)
4637!------------------------------------------------------------------------------!
4638    SUBROUTINE resize_array_3d_int8( var, ks, ke, js, je, is, ie )
4639
4640       IMPLICIT NONE
4641
4642       INTEGER(iwp) ::  je !< upper index bound along y direction
4643       INTEGER(iwp) ::  js !< lower index bound along y direction
4644       INTEGER(iwp) ::  ie !< upper index bound along x direction
4645       INTEGER(iwp) ::  is !< lower index bound along x direction
4646       INTEGER(iwp) ::  ke !< upper bound of treated array in z-direction 
4647       INTEGER(iwp) ::  ks !< lower bound of treated array in z-direction 
4648       
4649       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var     !< treated variable
4650       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE ::  var_tmp !< temporary copy
4651!
4652!--    Allocate temporary variable
4653       ALLOCATE( var_tmp(ks:ke,js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4654!
4655!--    Temporary copy of the variable
4656       var_tmp(ks:ke,js:je,is:ie) = var(ks:ke,js:je,is:ie)
4657!
4658!--    Resize the array
4659       DEALLOCATE( var )
4660       ALLOCATE( var(ks:ke,js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4661!
4662!--    Transfer temporary copy back to original array
4663       var(ks:ke,js:je,is:ie) = var_tmp(ks:ke,js:je,is:ie)
4664
4665    END SUBROUTINE resize_array_3d_int8
4666   
4667!------------------------------------------------------------------------------!
4668! Description:
4669! ------------
4670!> Resize 3D Real array: (:,nys:nyn,nxl:nxr) -> (:,nysg:nyng,nxlg:nxrg)
4671!------------------------------------------------------------------------------!
4672    SUBROUTINE resize_array_3d_real( var, ks, ke, js, je, is, ie )
4673
4674       IMPLICIT NONE
4675
4676       INTEGER(iwp) ::  je !< upper index bound along y direction
4677       INTEGER(iwp) ::  js !< lower index bound along y direction
4678       INTEGER(iwp) ::  ie !< upper index bound along x direction
4679       INTEGER(iwp) ::  is !< lower index bound along x direction
4680       INTEGER(iwp) ::  ke !< upper bound of treated array in z-direction 
4681       INTEGER(iwp) ::  ks !< lower bound of treated array in z-direction 
4682       
4683       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  var     !< treated variable
4684       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  var_tmp !< temporary copy
4685!
4686!--    Allocate temporary variable
4687       ALLOCATE( var_tmp(ks:ke,js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4688!
4689!--    Temporary copy of the variable
4690       var_tmp(ks:ke,js:je,is:ie) = var(ks:ke,js:je,is:ie)
4691!
4692!--    Resize the array
4693       DEALLOCATE( var )
4694       ALLOCATE( var(ks:ke,js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4695!
4696!--    Transfer temporary copy back to original array
4697       var(ks:ke,js:je,is:ie) = var_tmp(ks:ke,js:je,is:ie)
4698
4699    END SUBROUTINE resize_array_3d_real
4700   
4701!------------------------------------------------------------------------------!
4702! Description:
4703! ------------
4704!> Resize 4D Real array: (:,:,nys:nyn,nxl:nxr) -> (:,nysg:nyng,nxlg:nxrg)
4705!------------------------------------------------------------------------------!
4706    SUBROUTINE resize_array_4d_real( var, k1s, k1e, k2s, k2e, js, je, is, ie )
4707
4708       IMPLICIT NONE
4709       
4710       INTEGER(iwp) ::  je  !< upper index bound along y direction
4711       INTEGER(iwp) ::  js  !< lower index bound along y direction
4712       INTEGER(iwp) ::  ie  !< upper index bound along x direction
4713       INTEGER(iwp) ::  is  !< lower index bound along x direction
4714       INTEGER(iwp) ::  k1e !< upper bound of treated array in z-direction 
4715       INTEGER(iwp) ::  k1s !< lower bound of treated array in z-direction
4716       INTEGER(iwp) ::  k2e !< upper bound of treated array along parameter space 
4717       INTEGER(iwp) ::  k2s !< lower bound of treated array along parameter space 
4718       
4719       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  var     !< treated variable
4720       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  var_tmp !< temporary copy
4721!
4722!--    Allocate temporary variable
4723       ALLOCATE( var_tmp(k1s:k1e,k2s:k2e,js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4724!
4725!--    Temporary copy of the variable
4726       var_tmp(k1s:k1e,k2s:k2e,js:je,is:ie) = var(k1s:k1e,k2s:k2e,js:je,is:ie)
4727!
4728!--    Resize the array
4729       DEALLOCATE( var )
4730       ALLOCATE( var(k1s:k1e,k2s:k2e,js-nbgp:je+nbgp,is-nbgp:ie+nbgp) )
4731!
4732!--    Transfer temporary copy back to original array
4733       var(k1s:k1e,k2s:k2e,js:je,is:ie) = var_tmp(k1s:k1e,k2s:k2e,js:je,is:ie)
4734
4735    END SUBROUTINE resize_array_4d_real
4736   
4737!------------------------------------------------------------------------------!
4738! Description:
4739! ------------
4740!> Vertical interpolation and extrapolation of 1D variables.
4741!------------------------------------------------------------------------------!
4742    SUBROUTINE netcdf_data_input_interpolate_1d( var, z_grid, z_file)
4743
4744       IMPLICIT NONE
4745
4746       INTEGER(iwp) ::  k       !< running index z-direction file
4747       INTEGER(iwp) ::  kk      !< running index z-direction stretched model grid
4748       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
4749       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
4750
4751       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
4752       REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid
4753       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var      !< treated variable
4754       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var_tmp  !< temporary variable
4755
4756
4757       kl = LBOUND(var,1)
4758       ku = UBOUND(var,1)
4759       ALLOCATE( var_tmp(kl:ku) )
4760
4761       DO  k = kl, ku
4762
4763          kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
4764
4765          IF ( kk < ku )  THEN
4766             IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
4767                var_tmp(k) = var(kk) +                                         &
4768                                       ( var(kk+1)        - var(kk)    ) /     &
4769                                       ( z_file(kk+1)     - z_file(kk) ) *     &
4770                                       ( z_grid(k)        - z_file(kk) )
4771
4772             ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
4773                var_tmp(k) = var(kk-1) +                                       &
4774                                         ( var(kk)     - var(kk-1)    ) /      &
4775                                         ( z_file(kk)  - z_file(kk-1) ) *      &
4776                                         ( z_grid(k)   - z_file(kk-1) )
4777             ENDIF
4778!
4779!--       Extrapolate
4780          ELSE
4781
4782             var_tmp(k) = var(ku) +   ( var(ku)    - var(ku-1)      ) /        &
4783                                      ( z_file(ku) - z_file(ku-1)   ) *        &
4784                                      ( z_grid(k)  - z_file(ku)     )
4785
4786          ENDIF
4787
4788       ENDDO
4789       var(:) = var_tmp(:)
4790
4791       DEALLOCATE( var_tmp )
4792
4793
4794    END SUBROUTINE netcdf_data_input_interpolate_1d
4795
4796
4797!------------------------------------------------------------------------------!
4798! Description:
4799! ------------
4800!> Vertical interpolation and extrapolation of 1D variables from Inifor grid
4801!> onto Palm grid, where both have same dimension. Please note, the passed
4802!> paramter list in 1D version is different compared to 2D version.
4803!------------------------------------------------------------------------------!
4804    SUBROUTINE netcdf_data_input_interpolate_1d_soil( var, var_file,           &
4805                                                      z_grid, z_file,          &
4806                                                      nzb_var, nzt_var,        &
4807                                                      nzb_file, nzt_file )
4808
4809       IMPLICIT NONE
4810
4811       INTEGER(iwp) ::  k        !< running index z-direction file
4812       INTEGER(iwp) ::  kk       !< running index z-direction stretched model grid
4813       INTEGER(iwp) ::  ku       !< upper index bound along z-direction for varialbe from file
4814       INTEGER(iwp) ::  nzb_var  !< lower bound of final array
4815       INTEGER(iwp) ::  nzt_var  !< upper bound of final array
4816       INTEGER(iwp) ::  nzb_file !< lower bound of file array
4817       INTEGER(iwp) ::  nzt_file !< upper bound of file array
4818
4819!        LOGICAL, OPTIONAL ::  zsoil !< flag indicating reverse z-axis, i.e. zsoil instead of height, e.g. in case of ocean or soil
4820
4821       REAL(wp), DIMENSION(nzb_var:nzt_var)   ::  z_grid   !< grid levels on numeric grid
4822       REAL(wp), DIMENSION(nzb_file:nzt_file) ::  z_file   !< grid levels on file grid
4823       REAL(wp), DIMENSION(nzb_var:nzt_var)   ::  var      !< treated variable
4824       REAL(wp), DIMENSION(nzb_file:nzt_file) ::  var_file !< temporary variable
4825
4826       ku = nzt_file
4827
4828       DO  k = nzb_var, nzt_var
4829!
4830!--       Determine index on Inifor grid which is closest to the actual height
4831          kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
4832!
4833!--       If closest index on Inifor grid is smaller than top index,
4834!--       interpolate the data
4835          IF ( kk < nzt_file )  THEN
4836             IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
4837                var(k) = var_file(kk) + ( var_file(kk+1) - var_file(kk) ) /    &
4838                                        ( z_file(kk+1)   - z_file(kk)   ) *    &
4839                                        ( z_grid(k)      - z_file(kk)   )
4840
4841             ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
4842                var(k) = var_file(kk-1) + ( var_file(kk) - var_file(kk-1) ) /  &
4843                                          ( z_file(kk)   - z_file(kk-1)   ) *  &
4844                                          ( z_grid(k)    - z_file(kk-1)   )
4845             ENDIF
4846!
4847!--       Extrapolate if actual height is above the highest Inifor level
4848          ELSE
4849             var(k) = var_file(ku) + ( var_file(ku) - var_file(ku-1) ) /       &
4850                                     ( z_file(ku)   - z_file(ku-1)   ) *       &
4851                                     ( z_grid(k)    - z_file(ku)     )
4852
4853          ENDIF
4854
4855       ENDDO
4856
4857    END SUBROUTINE netcdf_data_input_interpolate_1d_soil
4858
4859!------------------------------------------------------------------------------!
4860! Description:
4861! ------------
4862!> Vertical interpolation and extrapolation of 2D variables at lateral boundaries.
4863!------------------------------------------------------------------------------!
4864    SUBROUTINE netcdf_data_input_interpolate_2d( var, z_grid, z_file)
4865
4866       IMPLICIT NONE
4867
4868       INTEGER(iwp) ::  i       !< running index x- or y -direction
4869       INTEGER(iwp) ::  il      !< lower index bound along x- or y-direction
4870       INTEGER(iwp) ::  iu      !< upper index bound along x- or y-direction
4871       INTEGER(iwp) ::  k       !< running index z-direction file
4872       INTEGER(iwp) ::  kk      !< running index z-direction stretched model grid
4873       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
4874       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
4875
4876       REAL(wp), DIMENSION(:) ::  z_grid                  !< grid levels on numeric grid
4877       REAL(wp), DIMENSION(:) ::  z_file                  !< grid levels on file grid
4878       REAL(wp), DIMENSION(:,:), INTENT(INOUT) ::  var    !< treated variable
4879       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  var_tmp  !< temporary variable
4880
4881
4882       il = LBOUND(var,2)
4883       iu = UBOUND(var,2)
4884       kl = LBOUND(var,1)
4885       ku = UBOUND(var,1)
4886       ALLOCATE( var_tmp(kl:ku) )
4887
4888       DO  i = il, iu
4889          DO  k = kl, ku
4890
4891             kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
4892
4893             IF ( kk < ku )  THEN
4894                IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
4895                   var_tmp(k) = var(kk,i) +                                    &
4896                                          ( var(kk+1,i)      - var(kk,i)  ) /  &
4897                                          ( z_file(kk+1)     - z_file(kk) ) *  &
4898                                          ( z_grid(k)        - z_file(kk) )
4899
4900                ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
4901                   var_tmp(k) = var(kk-1,i) +                                  &
4902                                            ( var(kk,i)   - var(kk-1,i)  ) /   &
4903                                            ( z_file(kk)  - z_file(kk-1) ) *   &
4904                                            ( z_grid(k)   - z_file(kk-1) )
4905                ENDIF
4906!
4907!--          Extrapolate
4908             ELSE
4909
4910                var_tmp(k) = var(ku,i) + ( var(ku,i)  - var(ku-1,i)    ) /     &
4911                                         ( z_file(ku) - z_file(ku-1)   ) *     &
4912                                         ( z_grid(k)  - z_file(ku)     )
4913
4914             ENDIF
4915
4916          ENDDO
4917          var(:,i) = var_tmp(:)
4918
4919       ENDDO
4920
4921       DEALLOCATE( var_tmp )
4922
4923
4924    END SUBROUTINE netcdf_data_input_interpolate_2d
4925
4926!------------------------------------------------------------------------------!
4927! Description:
4928! ------------
4929!> Vertical interpolation and extrapolation of 3D variables.
4930!------------------------------------------------------------------------------!
4931    SUBROUTINE netcdf_data_input_interpolate_3d( var, z_grid, z_file )
4932
4933       IMPLICIT NONE
4934
4935       INTEGER(iwp) ::  i       !< running index x-direction
4936       INTEGER(iwp) ::  il      !< lower index bound along x-direction
4937       INTEGER(iwp) ::  iu      !< upper index bound along x-direction
4938       INTEGER(iwp) ::  j       !< running index y-direction
4939       INTEGER(iwp) ::  jl      !< lower index bound along x-direction
4940       INTEGER(iwp) ::  ju      !< upper index bound along x-direction
4941       INTEGER(iwp) ::  k       !< running index z-direction file
4942       INTEGER(iwp) ::  kk      !< running index z-direction stretched model grid
4943       INTEGER(iwp) ::  kl      !< lower index bound along z-direction
4944       INTEGER(iwp) ::  ku      !< upper index bound along z-direction
4945
4946       REAL(wp), DIMENSION(:) ::  z_grid                      !< grid levels on numeric grid
4947       REAL(wp), DIMENSION(:) ::  z_file                      !< grid levels on file grid
4948       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var      !< treated variable
4949       REAL(wp), DIMENSION(:), ALLOCATABLE       ::  var_tmp  !< temporary variable
4950
4951       il = LBOUND(var,3)
4952       iu = UBOUND(var,3)
4953       jl = LBOUND(var,2)
4954       ju = UBOUND(var,2)
4955       kl = LBOUND(var,1)
4956       ku = UBOUND(var,1)
4957
4958       ALLOCATE( var_tmp(kl:ku) )
4959
4960       DO  i = il, iu
4961          DO  j = jl, ju
4962             DO  k = kl, ku
4963
4964                kk = MINLOC( ABS( z_file - z_grid(k) ), DIM = 1 )
4965
4966                IF ( kk < ku )  THEN
4967                   IF ( z_file(kk) - z_grid(k) <= 0.0_wp )  THEN
4968                      var_tmp(k) = var(kk,j,i) +                               &
4969                                             ( var(kk+1,j,i) - var(kk,j,i) ) / &
4970                                             ( z_file(kk+1)  - z_file(kk)  ) * &
4971                                             ( z_grid(k)     - z_file(kk)  )
4972
4973                   ELSEIF ( z_file(kk) - z_grid(k) > 0.0_wp )  THEN
4974                      var_tmp(k) = var(kk-1,j,i) +                             &
4975                                             ( var(kk,j,i) - var(kk-1,j,i) ) / &
4976                                             ( z_file(kk)  - z_file(kk-1)  ) * &
4977                                             ( z_grid(k)   - z_file(kk-1)  )
4978                   ENDIF
4979!
4980!--             Extrapolate
4981                ELSE
4982                   var_tmp(k) = var(ku,j,i) +                                  &
4983                                       ( var(ku,j,i)  - var(ku-1,j,i)   ) /    &
4984                                       ( z_file(ku)   - z_file(ku-1)    ) *    &
4985                                       ( z_grid(k)    - z_file(ku)      )
4986
4987                ENDIF
4988             ENDDO
4989             var(:,j,i) = var_tmp(:)
4990          ENDDO
4991       ENDDO
4992
4993       DEALLOCATE( var_tmp )
4994
4995
4996    END SUBROUTINE netcdf_data_input_interpolate_3d
4997
4998!------------------------------------------------------------------------------!
4999! Description:
5000! ------------
5001!> Checks if a given variables is on file
5002!------------------------------------------------------------------------------!
5003    FUNCTION check_existence( vars_in_file, var_name )
5004
5005       IMPLICIT NONE
5006
5007       CHARACTER(LEN=*) ::  var_name                   !< variable to be checked
5008       CHARACTER(LEN=*), DIMENSION(:) ::  vars_in_file !< list of variables in file
5009
5010       INTEGER(iwp) ::  i                              !< loop variable
5011
5012       LOGICAL ::  check_existence                     !< flag indicating whether a variable exist or not - actual return value
5013
5014       i = 1
5015       check_existence = .FALSE.
5016       DO  WHILE ( i <= SIZE( vars_in_file ) )
5017          check_existence = TRIM( vars_in_file(i) ) == TRIM( var_name )  .OR.  &
5018                            check_existence
5019          i = i + 1
5020       ENDDO
5021
5022       RETURN
5023
5024    END FUNCTION check_existence
5025
5026
5027!------------------------------------------------------------------------------!
5028! Description:
5029! ------------
5030!> Closes an existing netCDF file.
5031!------------------------------------------------------------------------------!
5032    SUBROUTINE close_input_file( id )
5033#if defined( __netcdf )
5034
5035       USE pegrid
5036
5037       IMPLICIT NONE
5038
5039       INTEGER(iwp), INTENT(INOUT)        ::  id        !< file id
5040
5041       nc_stat = NF90_CLOSE( id )
5042       CALL handle_error( 'close', 540 )
5043#endif
5044    END SUBROUTINE close_input_file
5045
5046!------------------------------------------------------------------------------!
5047! Description:
5048! ------------
5049!> Opens an existing netCDF file for reading only and returns its id.
5050!------------------------------------------------------------------------------!
5051    SUBROUTINE open_read_file( filename, id )
5052#if defined( __netcdf )
5053
5054       USE pegrid
5055
5056       IMPLICIT NONE
5057
5058       CHARACTER (LEN=*), INTENT(IN) ::  filename  !< filename
5059       INTEGER(iwp), INTENT(INOUT)   ::  id        !< file id
5060
5061#if defined( __netcdf4_parallel )
5062!
5063!--    If __netcdf4_parallel is defined, parrallel NetCDF will be used
5064!--    unconditionally
5065       nc_stat = NF90_OPEN( filename, IOR( NF90_WRITE, NF90_MPIIO ), id,  &
5066                            COMM = comm2d, INFO = MPI_INFO_NULL )
5067!
5068!--    Check for possible Netcdf 3 file.
5069       IF( nc_stat /= NF90_NOERR )  THEN
5070          nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
5071          collective_read = .FALSE.
5072       ELSE
5073          collective_read = .TRUE.
5074       ENDIF
5075#else
5076!      All MPI processes open und read
5077       nc_stat = NF90_OPEN( filename, NF90_NOWRITE, id )
5078#endif
5079
5080       CALL handle_error( 'open_read_file', 539 )
5081
5082#endif
5083    END SUBROUTINE open_read_file
5084
5085!------------------------------------------------------------------------------!
5086! Description:
5087! ------------
5088!> Reads global or variable-related attributes of type INTEGER (32-bit)
5089!------------------------------------------------------------------------------!
5090     SUBROUTINE get_attribute_int32( id, attribute_name, value, global,        &
5091                                     variable_name )
5092
5093       USE pegrid
5094
5095       IMPLICIT NONE
5096
5097       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
5098       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
5099
5100       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5101       INTEGER(iwp)                ::  id_var           !< variable id
5102       INTEGER(iwp), INTENT(INOUT) ::  value            !< read value
5103
5104       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
5105#if defined( __netcdf )
5106
5107!
5108!--    Read global attribute
5109       IF ( global )  THEN
5110          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
5111          CALL handle_error( 'get_attribute_int32 global', 522, attribute_name )
5112!
5113!--    Read attributes referring to a single variable. Therefore, first inquire
5114!--    variable id
5115       ELSE
5116          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5117          CALL handle_error( 'get_attribute_int32', 522, attribute_name )
5118          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
5119          CALL handle_error( 'get_attribute_int32', 522, attribute_name )
5120       ENDIF
5121#endif
5122    END SUBROUTINE get_attribute_int32
5123
5124!------------------------------------------------------------------------------!
5125! Description:
5126! ------------
5127!> Reads global or variable-related attributes of type INTEGER (8-bit)
5128!------------------------------------------------------------------------------!
5129     SUBROUTINE get_attribute_int8( id, attribute_name, value, global,         &
5130                                    variable_name )
5131
5132       USE pegrid
5133
5134       IMPLICIT NONE
5135
5136       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
5137       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
5138
5139       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5140       INTEGER(iwp)                ::  id_var           !< variable id
5141       INTEGER(KIND=1), INTENT(INOUT) ::  value         !< read value
5142
5143       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
5144#if defined( __netcdf )
5145
5146!
5147!--    Read global attribute
5148       IF ( global )  THEN
5149          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
5150          CALL handle_error( 'get_attribute_int8 global', 523, attribute_name )
5151!
5152!--    Read attributes referring to a single variable. Therefore, first inquire
5153!--    variable id
5154       ELSE
5155          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5156          CALL handle_error( 'get_attribute_int8', 523, attribute_name )
5157          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
5158          CALL handle_error( 'get_attribute_int8', 523, attribute_name )
5159       ENDIF
5160#endif
5161    END SUBROUTINE get_attribute_int8
5162
5163!------------------------------------------------------------------------------!
5164! Description:
5165! ------------
5166!> Reads global or variable-related attributes of type REAL
5167!------------------------------------------------------------------------------!
5168     SUBROUTINE get_attribute_real( id, attribute_name, value, global,         &
5169                                    variable_name )
5170
5171       USE pegrid
5172
5173       IMPLICIT NONE
5174
5175       CHARACTER(LEN=*)            ::  attribute_name   !< attribute name
5176       CHARACTER(LEN=*), OPTIONAL  ::  variable_name    !< variable name
5177
5178       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5179       INTEGER(iwp)                ::  id_var           !< variable id
5180
5181       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
5182
5183       REAL(wp), INTENT(INOUT)     ::  value            !< read value
5184#if defined( __netcdf )
5185
5186
5187!
5188!-- Read global attribute
5189       IF ( global )  THEN
5190          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
5191          CALL handle_error( 'get_attribute_real global', 524, attribute_name )
5192!
5193!-- Read attributes referring to a single variable. Therefore, first inquire
5194!-- variable id
5195       ELSE
5196          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5197          CALL handle_error( 'get_attribute_real', 524, attribute_name )
5198          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
5199          CALL handle_error( 'get_attribute_real', 524, attribute_name )
5200       ENDIF
5201#endif
5202    END SUBROUTINE get_attribute_real
5203
5204!------------------------------------------------------------------------------!
5205! Description:
5206! ------------
5207!> Reads global or variable-related attributes of type CHARACTER
5208!> Remark: reading attributes of type NF_STRING return an error code 56 -
5209!> Attempt to convert between text & numbers.
5210!------------------------------------------------------------------------------!
5211     SUBROUTINE get_attribute_string( id, attribute_name, value, global,       &
5212                                      variable_name, no_abort )
5213
5214       USE pegrid
5215
5216       IMPLICIT NONE
5217
5218       CHARACTER(LEN=*)                ::  attribute_name   !< attribute name
5219       CHARACTER(LEN=*), OPTIONAL      ::  variable_name    !< variable name
5220       CHARACTER(LEN=*), INTENT(INOUT) ::  value            !< read value
5221
5222       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5223       INTEGER(iwp)                ::  id_var           !< variable id
5224
5225       LOGICAL ::  check_error                          !< flag indicating if handle_error shall be checked
5226       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
5227       LOGICAL, INTENT(IN), OPTIONAL ::  no_abort       !< flag indicating if errors should be checked
5228#if defined( __netcdf )
5229
5230       IF ( PRESENT( no_abort ) )  THEN
5231          check_error = no_abort
5232       ELSE
5233          check_error = .TRUE.
5234       ENDIF
5235!
5236!--    Read global attribute
5237       IF ( global )  THEN
5238          nc_stat = NF90_GET_ATT( id, NF90_GLOBAL, TRIM( attribute_name ), value )
5239          IF ( check_error)  CALL handle_error( 'get_attribute_string global', 525, attribute_name )
5240!
5241!--    Read attributes referring to a single variable. Therefore, first inquire
5242!--    variable id
5243       ELSE
5244          nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5245          IF ( check_error)  CALL handle_error( 'get_attribute_string', 525, attribute_name )
5246
5247          nc_stat = NF90_GET_ATT( id, id_var, TRIM( attribute_name ), value )
5248          IF ( check_error)  CALL handle_error( 'get_attribute_string',525, attribute_name )
5249
5250       ENDIF
5251#endif
5252    END SUBROUTINE get_attribute_string
5253
5254
5255
5256!------------------------------------------------------------------------------!
5257! Description:
5258! ------------
5259!> Get dimension array for a given dimension
5260!------------------------------------------------------------------------------!
5261     SUBROUTINE netcdf_data_input_get_dimension_length( id, dim_len,           &
5262                                                        variable_name )
5263       USE pegrid
5264
5265       IMPLICIT NONE
5266
5267       CHARACTER(LEN=*)            ::  variable_name    !< dimension name
5268       CHARACTER(LEN=100)          ::  dum              !< dummy variable to receive return character
5269
5270       INTEGER(iwp)                ::  dim_len          !< dimension size
5271       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5272       INTEGER(iwp)                ::  id_dim           !< dimension id
5273
5274#if defined( __netcdf )
5275!
5276!--    First, inquire dimension ID
5277       nc_stat = NF90_INQ_DIMID( id, TRIM( variable_name ), id_dim )
5278       CALL handle_error( 'netcdf_data_input_get_dimension_length', 526,       &
5279                          variable_name )
5280!
5281!--    Inquire dimension length
5282       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim, dum, LEN = dim_len )
5283       CALL handle_error( 'netcdf_data_input_get_dimension_length', 526,       &
5284                          variable_name )
5285
5286#endif
5287    END SUBROUTINE netcdf_data_input_get_dimension_length
5288
5289!------------------------------------------------------------------------------!
5290! Description:
5291! ------------
5292!> Routine for reading-in a character string from the chem emissions netcdf
5293!> input file. 
5294!------------------------------------------------------------------------------!
5295    SUBROUTINE get_variable_string( id, variable_name, var_string, names_number)
5296#if defined( __netcdf )
5297
5298       USE indices
5299       USE pegrid
5300
5301       IMPLICIT NONE
5302
5303       CHARACTER (LEN=25), ALLOCATABLE, DIMENSION(:), INTENT(INOUT)  :: var_string
5304
5305       CHARACTER(LEN=*)                                              :: variable_name          !> variable name
5306
5307       CHARACTER (LEN=1), ALLOCATABLE, DIMENSION(:,:)                :: tmp_var_string         !> variable to be read
5308
5309
5310       INTEGER(iwp), INTENT(IN)                                      :: id                     !> file id
5311
5312       INTEGER(iwp), INTENT(IN)                                      :: names_number           !> number of names
5313
5314       INTEGER(iwp)                                                  :: id_var                 !> variable id
5315
5316       INTEGER(iwp)                                                  :: i,j                    !> index to go through the length of the dimensions
5317
5318       INTEGER(iwp)                                                  :: max_string_length=25   !> this is both the maximum length of a name, but also 
5319                                                                                            ! the number of the components of the first dimensions
5320                                                                                            ! (rows)
5321
5322
5323       ALLOCATE(tmp_var_string(max_string_length,names_number))
5324
5325       ALLOCATE(var_string(names_number))
5326
5327    !-- Inquire variable id
5328       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5329
5330
5331    !-- Get variable
5332    !-- Start cycle over the emission species
5333       DO i = 1, names_number 
5334       !-- read the first letter of each component
5335          nc_stat = NF90_GET_VAR( id, id_var, var_string(i), start = (/ 1,i /), &
5336                                 count = (/ 1,1 /) )
5337          CALL handle_error( 'get_variable_string', 701 )
5338
5339       !-- Start cycle over charachters
5340          DO j = 1, max_string_length
5341                       
5342          !-- read the rest of the components of the name
5343             nc_stat = NF90_GET_VAR( id, id_var, tmp_var_string(j,i), start = (/ j,i /),&
5344                                     count = (/ 1,1 /) )
5345             CALL handle_error( 'get_variable_string', 702 )
5346
5347             IF ( iachar(tmp_var_string(j,i) ) == 0 ) THEN
5348                  tmp_var_string(j,i)=''
5349             ENDIF
5350
5351             IF ( j>1 ) THEN
5352             !-- Concatenate first letter of the name and the others
5353                var_string(i)=TRIM(var_string(i)) // TRIM(tmp_var_string(j,i))
5354
5355             ENDIF
5356          ENDDO 
5357       ENDDO
5358
5359#endif
5360    END SUBROUTINE get_variable_string
5361
5362!------------------------------------------------------------------------------!
5363! Description:
5364! ------------
5365!> Reads a character variable in a 1D array
5366!------------------------------------------------------------------------------!
5367     SUBROUTINE get_variable_1d_char( id, variable_name, var )
5368
5369       USE pegrid
5370
5371       IMPLICIT NONE
5372
5373       CHARACTER(LEN=*)            ::  variable_name          !< variable name
5374       CHARACTER(LEN=*), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
5375
5376       INTEGER(iwp)                ::  i                !< running index over variable dimension
5377       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5378       INTEGER(iwp)                ::  id_var           !< dimension id
5379       
5380       INTEGER(iwp), DIMENSION(2)  ::  dimid            !< dimension IDs
5381       INTEGER(iwp), DIMENSION(2)  ::  dimsize          !< dimension size
5382
5383#if defined( __netcdf )
5384
5385!
5386!--    First, inquire variable ID
5387       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5388       CALL handle_error( 'get_variable_1d_int', 527, variable_name )
5389!
5390!--    Inquire dimension IDs
5391       nc_stat = NF90_INQUIRE_VARIABLE( id, id_var, dimids = dimid(1:2) )
5392       CALL handle_error( 'get_variable_1d_char', 527, variable_name )
5393!
5394!--    Read dimesnion length
5395       nc_stat = NF90_INQUIRE_DIMENSION( id, dimid(1), LEN = dimsize(1) )
5396       nc_stat = NF90_INQUIRE_DIMENSION( id, dimid(2), LEN = dimsize(2) )
5397       
5398!
5399!--    Read character array. Note, each element is read individually, in order
5400!--    to better separate single strings.
5401       DO  i = 1, dimsize(2)
5402          nc_stat = NF90_GET_VAR( id, id_var, var(i),                          &
5403                                  start = (/ 1, i /),                          &
5404                                  count = (/ dimsize(1), 1 /) )
5405          CALL handle_error( 'get_variable_1d_char', 527, variable_name )
5406       ENDDO     
5407                         
5408#endif
5409    END SUBROUTINE get_variable_1d_char
5410
5411   
5412!------------------------------------------------------------------------------!
5413! Description:
5414! ------------
5415!> Reads a 1D integer variable from file.
5416!------------------------------------------------------------------------------!
5417     SUBROUTINE get_variable_1d_int( id, variable_name, var )
5418
5419       USE pegrid
5420
5421       IMPLICIT NONE
5422
5423       CHARACTER(LEN=*)            ::  variable_name    !< variable name
5424
5425       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5426       INTEGER(iwp)                ::  id_var           !< dimension id
5427
5428       INTEGER(iwp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
5429#if defined( __netcdf )
5430
5431!
5432!--    First, inquire variable ID
5433       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5434       CALL handle_error( 'get_variable_1d_int', 527, variable_name )
5435!
5436!--    Inquire dimension length
5437       nc_stat = NF90_GET_VAR( id, id_var, var )
5438       CALL handle_error( 'get_variable_1d_int', 527, variable_name )
5439
5440#endif
5441    END SUBROUTINE get_variable_1d_int
5442
5443!------------------------------------------------------------------------------!
5444! Description:
5445! ------------
5446!> Reads a 1D float variable from file.
5447!------------------------------------------------------------------------------!
5448     SUBROUTINE get_variable_1d_real( id, variable_name, var )
5449
5450       USE pegrid
5451
5452       IMPLICIT NONE
5453
5454       CHARACTER(LEN=*)            ::  variable_name    !< variable name
5455
5456       INTEGER(iwp), INTENT(IN)    ::  id               !< file id
5457       INTEGER(iwp)                ::  id_var           !< dimension id
5458
5459       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var    !< variable to be read
5460#if defined( __netcdf )
5461
5462!
5463!--    First, inquire variable ID
5464       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5465       CALL handle_error( 'get_variable_1d_real', 528, variable_name )
5466!
5467!--    Inquire dimension length
5468       nc_stat = NF90_GET_VAR( id, id_var, var )
5469       CALL handle_error( 'get_variable_1d_real', 528, variable_name )
5470
5471#endif
5472    END SUBROUTINE get_variable_1d_real
5473
5474
5475!------------------------------------------------------------------------------!
5476! Description:
5477! ------------
5478!> Reads a time-dependent 1D float variable from file.
5479!------------------------------------------------------------------------------!
5480    SUBROUTINE get_variable_pr( id, variable_name, t, var )
5481#if defined( __netcdf )
5482
5483       USE pegrid
5484
5485       IMPLICIT NONE
5486
5487       CHARACTER(LEN=*)                      ::  variable_name    !< variable name
5488
5489       INTEGER(iwp), INTENT(IN)              ::  id               !< file id
5490       INTEGER(iwp), DIMENSION(1:2)          ::  id_dim           !< dimension ids
5491       INTEGER(iwp)                          ::  id_var           !< dimension id
5492       INTEGER(iwp)                          ::  n_file           !< number of data-points in file along z dimension
5493       INTEGER(iwp), INTENT(IN)              ::  t                !< timestep number
5494
5495       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
5496
5497!
5498!--    First, inquire variable ID
5499       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5500!
5501!--    Inquire dimension size of vertical dimension
5502       nc_stat = NF90_INQUIRE_VARIABLE( id, id_var, DIMIDS = id_dim )
5503       nc_stat = NF90_INQUIRE_DIMENSION( id, id_dim(1), LEN = n_file )
5504!
5505!--    Read variable.
5506       nc_stat = NF90_GET_VAR( id, id_var, var,                                &
5507                               start = (/ 1,      t     /),                    &
5508                               count = (/ n_file, 1     /) )
5509       CALL handle_error( 'get_variable_pr', 529, variable_name )
5510
5511#endif
5512    END SUBROUTINE get_variable_pr
5513
5514
5515!------------------------------------------------------------------------------!
5516! Description:
5517! ------------
5518!> Reads a 2D REAL variable from a file. Reading is done processor-wise,
5519!> i.e. each core reads its own domain in slices along x.
5520!------------------------------------------------------------------------------!
5521    SUBROUTINE get_variable_2d_real( id, variable_name, var, is, ie, js, je )
5522
5523       USE indices
5524       USE pegrid
5525
5526       IMPLICIT NONE
5527
5528       CHARACTER(LEN=*)              ::  variable_name   !< variable name
5529
5530       INTEGER(iwp)                  ::  i               !< running index along x direction
5531       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
5532       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
5533       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
5534       INTEGER(iwp)                  ::  id_var          !< variable id
5535       INTEGER(iwp)                  ::  j               !< running index along y direction
5536       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
5537       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
5538       
5539       REAL(wp), DIMENSION(:,:), ALLOCATABLE   ::  tmp   !< temporary variable to read data from file according
5540                                                         !< to its reverse memory access
5541       REAL(wp), DIMENSION(:,:), INTENT(INOUT) ::  var   !< variable to be read
5542#if defined( __netcdf )
5543!
5544!--    Inquire variable id
5545       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5546!
5547!--    Check for collective read-operation and set respective NetCDF flags if
5548!--    required.
5549       IF ( collective_read )  THEN
5550#if defined( __netcdf4_parallel )
5551          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
5552#endif
5553       ENDIF
5554
5555!
5556!-- Allocate temporary variable according to memory access on file.
5557       ALLOCATE( tmp(is:ie,js:je) )
5558!
5559!-- Get variable
5560       nc_stat = NF90_GET_VAR( id, id_var, tmp,            &
5561                      start = (/ is+1,      js+1 /),       &
5562                      count = (/ ie-is + 1, je-js+1 /) )   
5563          CALL handle_error( 'get_variable_2d_real', 530, variable_name )
5564!
5565!-- Resort data. Please note, dimension subscripts of var all start at 1.
5566          DO  i = is, ie 
5567             DO  j = js, je 
5568                var(j-js+1,i-is+1) = tmp(i,j)
5569             ENDDO
5570          ENDDO
5571       
5572          DEALLOCATE( tmp )
5573
5574#endif
5575    END SUBROUTINE get_variable_2d_real
5576
5577!------------------------------------------------------------------------------!
5578! Description:
5579! ------------
5580!> Reads a 2D 32-bit INTEGER variable from file. Reading is done processor-wise,
5581!> i.e. each core reads its own domain in slices along x.
5582!------------------------------------------------------------------------------!
5583    SUBROUTINE get_variable_2d_int32( id, variable_name, var, is, ie, js, je )
5584
5585       USE indices
5586       USE pegrid
5587
5588       IMPLICIT NONE
5589
5590       CHARACTER(LEN=*)              ::  variable_name   !< variable name
5591
5592       INTEGER(iwp)                  ::  i               !< running index along x direction
5593       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
5594       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
5595       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
5596       INTEGER(iwp)                  ::  id_var          !< variable id
5597       INTEGER(iwp)                  ::  j               !< running index along y direction
5598       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
5599       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
5600       
5601       INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
5602                                                            !< to its reverse memory access
5603       INTEGER(iwp), DIMENSION(:,:), INTENT(INOUT) ::  var  !< variable to be read
5604#if defined( __netcdf )
5605!
5606!--    Inquire variable id
5607       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5608!
5609!--    Check for collective read-operation and set respective NetCDF flags if
5610!--    required.
5611       IF ( collective_read )  THEN
5612#if defined( __netcdf4_parallel )       
5613          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
5614#endif
5615       ENDIF
5616!
5617!--    Allocate temporary variable according to memory access on file.
5618       ALLOCATE( tmp(is:ie,js:je) )
5619!
5620!--    Get variable
5621       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
5622                               start = (/ is+1,      js+1 /),                  &
5623                               count = (/ ie-is + 1, je-js+1 /) )   
5624                               
5625       CALL handle_error( 'get_variable_2d_int32', 531, variable_name )                             
5626!
5627!--    Resort data. Please note, dimension subscripts of var all start at 1.
5628       DO  i = is, ie 
5629          DO  j = js, je 
5630             var(j-js+1,i-is+1) = tmp(i,j)
5631          ENDDO
5632       ENDDO
5633       
5634       DEALLOCATE( tmp )
5635
5636#endif
5637    END SUBROUTINE get_variable_2d_int32
5638
5639!------------------------------------------------------------------------------!
5640! Description:
5641! ------------
5642!> Reads a 2D 8-bit INTEGER variable from file. Reading is done processor-wise,
5643!> i.e. each core reads its own domain in slices along x.
5644!------------------------------------------------------------------------------!
5645    SUBROUTINE get_variable_2d_int8( id, variable_name, var, is, ie, js, je )
5646
5647       USE indices
5648       USE pegrid
5649
5650       IMPLICIT NONE
5651
5652       CHARACTER(LEN=*)              ::  variable_name   !< variable name
5653
5654       INTEGER(iwp)                  ::  i               !< running index along x direction
5655       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
5656       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
5657       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
5658       INTEGER(iwp)                  ::  id_var          !< variable id
5659       INTEGER(iwp)                  ::  j               !< running index along y direction
5660       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
5661       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
5662       
5663       INTEGER(KIND=1), DIMENSION(:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
5664                                                               !< to its reverse memory access
5665       INTEGER(KIND=1), DIMENSION(:,:), INTENT(INOUT) ::  var  !< variable to be read
5666#if defined( __netcdf )
5667!
5668!--    Inquire variable id
5669       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5670!
5671!--    Check for collective read-operation and set respective NetCDF flags if
5672!--    required.
5673       IF ( collective_read )  THEN
5674#if defined( __netcdf4_parallel )       
5675          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
5676#endif         
5677       ENDIF
5678!
5679!--    Allocate temporary variable according to memory access on file.
5680       ALLOCATE( tmp(is:ie,js:je) )
5681!
5682!--    Get variable
5683       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
5684                               start = (/ is+1,      js+1 /),                  &
5685                               count = (/ ie-is + 1, je-js+1 /) )   
5686                               
5687       CALL handle_error( 'get_variable_2d_int8', 532, variable_name )
5688!
5689!--    Resort data. Please note, dimension subscripts of var all start at 1.
5690       DO  i = is, ie 
5691          DO  j = js, je 
5692             var(j-js+1,i-is+1) = tmp(i,j)
5693          ENDDO
5694       ENDDO
5695       
5696       DEALLOCATE( tmp )
5697
5698#endif
5699    END SUBROUTINE get_variable_2d_int8
5700
5701
5702!------------------------------------------------------------------------------!
5703! Description:
5704! ------------
5705!> Reads a 3D 8-bit INTEGER variable from file.
5706!------------------------------------------------------------------------------!
5707    SUBROUTINE get_variable_3d_int8( id, variable_name, var, is, ie, js, je,   &
5708                                     ks, ke )
5709
5710       USE indices
5711       USE pegrid
5712
5713       IMPLICIT NONE
5714
5715       CHARACTER(LEN=*)              ::  variable_name   !< variable name
5716
5717       INTEGER(iwp)                  ::  i               !< index along x direction
5718       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
5719       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
5720       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
5721       INTEGER(iwp)                  ::  id_var          !< variable id
5722       INTEGER(iwp)                  ::  j               !< index along y direction
5723       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
5724       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
5725       INTEGER(iwp)                  ::  k               !< index along any 3rd dimension
5726       INTEGER(iwp)                  ::  ke              !< start index of 3rd dimension
5727       INTEGER(iwp)                  ::  ks              !< end index of 3rd dimension
5728
5729       INTEGER(KIND=1), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
5730                                                                 !< to its reverse memory access
5731
5732       INTEGER(KIND=1), DIMENSION(:,:,:), INTENT(INOUT) ::  var  !< variable to be read
5733#if defined( __netcdf )
5734
5735!
5736!--    Inquire variable id
5737       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5738!
5739!--    Check for collective read-operation and set respective NetCDF flags if
5740!--    required.
5741       IF ( collective_read )  THEN
5742#if defined( __netcdf4_parallel )
5743          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
5744#endif
5745       ENDIF
5746!
5747!--    Allocate temporary variable according to memory access on file.
5748       ALLOCATE( tmp(is:ie,js:je,ks:ke) )
5749!
5750!--    Get variable
5751       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
5752                               start = (/ is+1,    js+1,    ks+1 /),           &
5753                               count = (/ ie-is+1, je-js+1, ke-ks+1 /) )
5754
5755       CALL handle_error( 'get_variable_3d_int8', 533, variable_name )
5756!
5757!--    Resort data. Please note, dimension subscripts of var all start at 1.
5758       DO  i = is, ie 
5759          DO  j = js, je
5760             DO  k = ks, ke
5761                var(k-ks+1,j-js+1,i-is+1) = tmp(i,j,k)
5762             ENDDO
5763          ENDDO
5764       ENDDO
5765
5766       DEALLOCATE( tmp )
5767
5768#endif
5769    END SUBROUTINE get_variable_3d_int8
5770
5771
5772!------------------------------------------------------------------------------!
5773! Description:
5774! ------------
5775!> Reads a 3D float variable from file.
5776!------------------------------------------------------------------------------!
5777    SUBROUTINE get_variable_3d_real( id, variable_name, var, is, ie, js, je,   &
5778                                     ks, ke )
5779
5780       USE indices
5781       USE pegrid
5782
5783       IMPLICIT NONE
5784
5785       CHARACTER(LEN=*)              ::  variable_name   !< variable name
5786
5787       INTEGER(iwp)                  ::  i               !< index along x direction
5788       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
5789       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
5790       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
5791       INTEGER(iwp)                  ::  id_var          !< variable id
5792       INTEGER(iwp)                  ::  j               !< index along y direction
5793       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
5794       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
5795       INTEGER(iwp)                  ::  k               !< index along any 3rd dimension
5796       INTEGER(iwp)                  ::  ke              !< start index of 3rd dimension
5797       INTEGER(iwp)                  ::  ks              !< end index of 3rd dimension
5798
5799       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
5800                                                         !< to its reverse memory access
5801
5802       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var !< variable to be read
5803#if defined( __netcdf )
5804
5805!
5806!--    Inquire variable id
5807       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 
5808!
5809!--    Check for collective read-operation and set respective NetCDF flags if
5810!--    required.
5811       IF ( collective_read )  THEN
5812#if defined( __netcdf4_parallel )
5813          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
5814#endif
5815       ENDIF
5816!
5817!--    Allocate temporary variable according to memory access on file.
5818       ALLOCATE( tmp(is:ie,js:je,ks:ke) )
5819!
5820!--    Get variable
5821       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
5822                               start = (/ is+1,    js+1,    ks+1 /),           &
5823                               count = (/ ie-is+1, je-js+1, ke-ks+1 /) )   
5824
5825       CALL handle_error( 'get_variable_3d_real', 534, variable_name )
5826!
5827!--    Resort data. Please note, dimension subscripts of var all start at 1.
5828       DO  i = is, ie 
5829          DO  j = js, je
5830             DO  k = ks, ke
5831                var(k-ks+1,j-js+1,i-is+1) = tmp(i,j,k)
5832             ENDDO
5833          ENDDO
5834       ENDDO
5835
5836       DEALLOCATE( tmp )
5837
5838#endif
5839    END SUBROUTINE get_variable_3d_real
5840
5841!------------------------------------------------------------------------------!
5842! Description:
5843! ------------
5844!> Reads a 4D float variable from file.
5845!------------------------------------------------------------------------------!
5846    SUBROUTINE get_variable_4d_real( id, variable_name, var, is, ie, js, je,   &
5847                                     k1s, k1e, k2s, k2e )
5848
5849       USE indices
5850       USE pegrid
5851
5852       IMPLICIT NONE
5853
5854       CHARACTER(LEN=*)              ::  variable_name   !< variable name
5855
5856       INTEGER(iwp)                  ::  i               !< index along x direction
5857       INTEGER(iwp)                  ::  ie              !< start index for subdomain input along x direction
5858       INTEGER(iwp)                  ::  is              !< end index for subdomain input along x direction
5859       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
5860       INTEGER(iwp)                  ::  id_var          !< variable id
5861       INTEGER(iwp)                  ::  j               !< index along y direction
5862       INTEGER(iwp)                  ::  je              !< start index for subdomain input along y direction
5863       INTEGER(iwp)                  ::  js              !< end index for subdomain input along y direction
5864       INTEGER(iwp)                  ::  k1              !< index along 3rd direction
5865       INTEGER(iwp)                  ::  k1e             !< start index for 3rd dimension
5866       INTEGER(iwp)                  ::  k1s             !< end index for 3rd dimension
5867       INTEGER(iwp)                  ::  k2              !< index along 4th direction
5868       INTEGER(iwp)                  ::  k2e             !< start index for 4th dimension
5869       INTEGER(iwp)                  ::  k2s             !< end index for 4th dimension
5870
5871       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE   ::  tmp  !< temporary variable to read data from file according
5872                                                            !< to its reverse memory access
5873       REAL(wp), DIMENSION(:,:,:,:), INTENT(INOUT) ::  var  !< variable to be read
5874#if defined( __netcdf )
5875
5876!
5877!--    Inquire variable id
5878       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
5879!
5880!--    Check for collective read-operation and set respective NetCDF flags if
5881!--    required.
5882       IF ( collective_read )  THEN
5883#if defined( __netcdf4_parallel )       
5884          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
5885#endif
5886       ENDIF
5887
5888!
5889!-- Allocate temporary variable according to memory access on file.
5890       ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e) )
5891!
5892!-- Get variable
5893       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
5894                      start = (/ is+1,    js+1,    k1s+1,     k2s+1 /),        &
5895                      count = (/ ie-is+1, je-js+1, k1e-k1s+1, k2e-k2s+1 /) )
5896
5897          CALL handle_error( 'get_variable_4d_real', 535, variable_name )
5898!
5899!-- Resort data. Please note, dimension subscripts of var all start at 1.
5900       DO  i = is, ie 
5901          DO  j = js, je
5902             DO  k1 = k1s, k1e
5903                DO  k2 = k2s, k2e
5904                   var(k2-k2s+1,k1-k1s+1,j-js+1,i-is+1) = tmp(i,j,k1,k2)
5905                ENDDO
5906             ENDDO
5907          ENDDO
5908       ENDDO
5909
5910       DEALLOCATE( tmp )
5911
5912#endif
5913
5914    END SUBROUTINE get_variable_4d_real
5915
5916!------------------------------------------------------------------------------!
5917! Description:
5918! ------------
5919!> Reads a 4D float variable from file and store it to a 3-d variable.
5920!------------------------------------------------------------------------------!
5921    SUBROUTINE get_variable_4d_to_3d_real( id, variable_name, var, ns, is, ie, js, je,   &
5922                                           ks, ke )
5923
5924       USE indices
5925       USE pegrid
5926
5927       IMPLICIT NONE
5928
5929       CHARACTER(LEN=*)              ::  variable_name   !< variable name
5930
5931       INTEGER(iwp)                  ::  ns              !< start index for subdomain input along n dimension: ns coincides here with ne, since, we select only one value along the 1st dimension n
5932
5933       INTEGER(iwp)                  ::  i               !< index along x direction
5934       INTEGER(iwp)                  ::  ie              !< end index for subdomain input along x direction
5935       INTEGER(iwp)                  ::  is              !< start index for subdomain input along x direction
5936       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
5937       INTEGER(iwp)                  ::  id_var          !< variable id
5938       INTEGER(iwp)                  ::  j               !< index along y direction
5939       INTEGER(iwp)                  ::  je              !< end index for subdomain input along y direction
5940       INTEGER(iwp)                  ::  js              !< start index for subdomain input along y direction
5941       INTEGER(iwp)                  ::  k               !< index along any 4th dimension
5942       INTEGER(iwp)                  ::  ke              !< end index of 4th dimension
5943       INTEGER(iwp)                  ::  ks              !< start index of 4th dimension
5944       
5945       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
5946                                                         !< to its reverse memory access
5947
5948       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var  !< variable where the read data have to be stored: one dimension is reduced in the process
5949#if defined( __netcdf )
5950
5951!
5952!--    Inquire variable id
5953       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var ) 
5954!
5955!--    Check for collective read-operation and set respective NetCDF flags if
5956!--    required.
5957       IF ( collective_read )  THEN
5958          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
5959       ENDIF
5960
5961      !Temporary solution for reading emission chemistry files:
5962       IF ( id == id_emis ) THEN
5963
5964          !--    Allocate temporary variable according to memory access on file.
5965          ALLOCATE( tmp(is:ie,js:je,ks:ke) )
5966
5967          !--    Get variable
5968          nc_stat = NF90_GET_VAR( id, id_var, tmp(is:ie,js:je,ks:ke),                                &
5969                                  start = (/ ns, is,   js+1,   ks+1 /),                  &
5970                                  count = (/ 1, ie-is+1 , je-js+1, ke-ks+1 /) ) 
5971
5972          var=tmp(:,:,:)
5973
5974          CALL handle_error( 'get_variable_4d_to_3d_real', 536, variable_name )
5975 
5976          DEALLOCATE( tmp )
5977
5978       ELSE
5979!
5980!--       Allocate temporary variable according to memory access on file.
5981          ALLOCATE( tmp(is:ie,js:je,ks:ke) )
5982!
5983!--       Get variable
5984          nc_stat = NF90_GET_VAR( id, id_var, tmp,                             &
5985                                  start = (/ is+1,    js+1,    ks+1,   ns+1 /),&
5986                                  count = (/ ie-is+1, je-js+1, ke-ks+1, 1   /) )
5987
5988          CALL handle_error( 'get_variable_4d_to_3d_real', 536, variable_name )
5989!
5990!--       Resort data. Please note, dimension subscripts of var all start at 1.
5991          DO  i = is, ie
5992             DO  j = js, je
5993                DO  k = ks, ke
5994                   var(k-ks+1,j-js+1,i-is+1) = tmp(i,j,k)
5995                ENDDO
5996             ENDDO
5997          ENDDO
5998
5999         DEALLOCATE( tmp )
6000
6001       ENDIF
6002#endif
6003    END SUBROUTINE get_variable_4d_to_3d_real
6004
6005!------------------------------------------------------------------------------!
6006! Description:
6007! ------------
6008!> Reads a 3D float variables from dynamic driver, such as time-dependent xy-,
6009!> xz- or yz-boundary data as well as 3D initialization data. Please note,
6010!> the passed arguments are start indices and number of elements in each
6011!> dimension, which is in contrast to the other 3d versions where start- and
6012!> end indices are passed. The different handling of 3D dynamic variables is
6013!> due to its asymmetry for the u- and v component.
6014!------------------------------------------------------------------------------!
6015    SUBROUTINE get_variable_3d_real_dynamic( id, variable_name, var,           &
6016                                             i1s, i2s, i3s,                    &
6017                                             count_1, count_2, count_3,        &
6018                                             par_access )
6019                               
6020       USE indices
6021       USE pegrid
6022
6023       IMPLICIT NONE
6024
6025       CHARACTER(LEN=*)              ::  variable_name   !< variable name
6026
6027       LOGICAL                       ::  par_access      !< additional flag indicating whether parallel read operations should be performed or not
6028       
6029       INTEGER(iwp)                  ::  count_1         !< number of elements to be read along 1st dimension (with respect to file)
6030       INTEGER(iwp)                  ::  count_2         !< number of elements to be read along 2nd dimension (with respect to file)
6031       INTEGER(iwp)                  ::  count_3         !< number of elements to be read along 3rd dimension (with respect to file)
6032       INTEGER(iwp)                  ::  i1              !< running index along 1st dimension on file
6033       INTEGER(iwp)                  ::  i1s             !< start index for subdomain input along 1st dimension (with respect to file)
6034       INTEGER(iwp)                  ::  i2              !< running index along 2nd dimension on file       
6035       INTEGER(iwp)                  ::  i2s             !< start index for subdomain input along 2nd dimension (with respect to file)
6036       INTEGER(iwp)                  ::  i3              !< running index along 3rd dimension on file
6037       INTEGER(iwp)                  ::  i3s             !< start index of 3rd dimension, in dynamic file this is either time (2D boundary) or z (3D)
6038       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
6039       INTEGER(iwp)                  ::  id_var          !< variable id
6040       INTEGER(iwp)                  ::  lb1             !< lower bound of 1st dimension (with respect to file)
6041       INTEGER(iwp)                  ::  lb2             !< lower bound of 2nd dimension (with respect to file)
6042       INTEGER(iwp)                  ::  lb3             !< lower bound of 3rd dimension (with respect to file)
6043       INTEGER(iwp)                  ::  ub1             !< upper bound of 1st dimension (with respect to file)
6044       INTEGER(iwp)                  ::  ub2             !< upper bound of 2nd dimension (with respect to file)
6045       INTEGER(iwp)                  ::  ub3             !< upper bound of 3rd dimension (with respect to file)
6046
6047       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
6048                                                         !< to its reverse memory access
6049       
6050       REAL(wp), DIMENSION(:,:,:), INTENT(INOUT) ::  var !< input variable
6051       
6052#if defined( __netcdf )
6053!
6054!--    Inquire variable id.
6055       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
6056!
6057!--    Check for collective read-operation and set respective NetCDF flags if
6058!--    required.
6059!--    Please note, in contrast to the other input routines where each PEs
6060!--    reads its subdomain data, dynamic input data not by all PEs, only
6061!--    by those which encompass lateral model boundaries. Hence, collective
6062!--    read operations are only enabled for top-boundary data.
6063       IF ( collective_read  .AND.  par_access )  THEN
6064#if defined( __netcdf4_parallel )       
6065          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
6066#endif
6067       ENDIF   
6068!
6069!--    Allocate temporary variable according to memory access on file.
6070!--    Therefore, determine dimension bounds of input array.
6071       lb1 = LBOUND(var,3)
6072       ub1 = UBOUND(var,3)
6073       lb2 = LBOUND(var,2)
6074       ub2 = UBOUND(var,2)
6075       lb3 = LBOUND(var,1)
6076       ub3 = UBOUND(var,1)
6077       ALLOCATE( tmp(lb1:ub1,lb2:ub2,lb3:ub3) )
6078!
6079!--    Get variable
6080       nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
6081                               start = (/ i1s,     i2s,     i3s /),            &
6082                               count = (/ count_1, count_2, count_3 /) )
6083
6084       CALL handle_error( 'get_variable_3d_real_dynamic', 537, variable_name )
6085!
6086!--    Resort data. Please note, dimension subscripts of var all start at 1.
6087       DO  i3 = lb3, ub3
6088          DO i2 = lb2, ub2
6089             DO  i1 = lb1, ub1
6090                var(i3,i2,i1) = tmp(i1,i2,i3)
6091             ENDDO
6092          ENDDO
6093       ENDDO
6094       
6095       DEALLOCATE( tmp )       
6096#endif
6097    END SUBROUTINE get_variable_3d_real_dynamic
6098
6099!------------------------------------------------------------------------------!
6100! Description:
6101! ------------
6102!> Reads a 5D float variable from file and store it to a 4-d variable.
6103!------------------------------------------------------------------------------!
6104    SUBROUTINE get_variable_5d_to_4d_real( id, variable_name, var,              &
6105                                           ns, ts, te, is, ie, js, je, ks, ke )
6106
6107       USE indices
6108       USE pegrid
6109
6110       IMPLICIT NONE
6111
6112       CHARACTER(LEN=*)              ::  variable_name   !< variable name
6113
6114       INTEGER(iwp)                  ::  ns              !< start index for subdomain input along n dimension:
6115                                                         !< ns coincides here with ne, since, we select only one
6116                                                         !< value along the 1st dimension n
6117
6118       INTEGER(iwp)                  ::  t               !< index along t direction
6119       INTEGER(iwp)                  ::  te              !< end index for subdomain input along t direction
6120       INTEGER(iwp)                  ::  ts              !< start index for subdomain input along t direction
6121
6122       INTEGER(iwp)                  ::  i               !< index along x direction
6123       INTEGER(iwp)                  ::  ie              !< end index for subdomain input along x direction
6124       INTEGER(iwp)                  ::  is              !< start index for subdomain input along x direction
6125       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
6126       INTEGER(iwp)                  ::  id_var          !< variable id
6127       INTEGER(iwp)                  ::  j               !< index along y direction
6128       INTEGER(iwp)                  ::  je              !< end index for subdomain input along y direction
6129       INTEGER(iwp)                  ::  js              !< start index for subdomain input along y direction
6130       INTEGER(iwp)                  ::  k               !< index along any 5th dimension
6131       INTEGER(iwp)                  ::  ke              !< end index of 5th dimension
6132       INTEGER(iwp)                  ::  ks              !< start index of 5th dimension
6133       
6134       REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE   ::  tmp !< temporary variable to read data from file according
6135                                                           ! to its reverse memory access
6136       REAL(wp), DIMENSION(:,:,:,:), INTENT(INOUT) ::  var !< variable to be read
6137#if defined( __netcdf )
6138!
6139!--    Inquire variable id
6140       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
6141!
6142!--    Check for collective read-operation and set respective NetCDF flags if
6143!--    required.
6144       IF ( collective_read )  THEN
6145          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
6146       ENDIF
6147
6148      !Temporary solution for reading emission chemistry files:
6149       IF ( id == id_emis ) THEN
6150
6151          !--    Allocate temporary variable according to memory access on file.
6152          ALLOCATE( tmp(ts:te,1,js+1:je+1,ks+1:ke+1) )
6153
6154          !--    Get variable
6155          nc_stat = NF90_GET_VAR( id, id_var, tmp(ts:te,1,js+1:je+1,ks+1:ke+1),               &
6156                                  start = (/ ns, ts,  1,   js+1,   ks+1 /),                  &
6157                                  count = (/ 1, te-ts+1, 1, je-js+1, ke-ks+1 /) ) 
6158
6159          var=tmp
6160
6161          CALL handle_error( 'get_variable_5d_to_4d_real', 538, variable_name )
6162 
6163          DEALLOCATE( tmp )
6164
6165       !>  Original Subroutine part
6166       ELSE
6167!
6168!--    Allocate temporary variable according to memory access on file.
6169          ALLOCATE( tmp(ks:ke,js:je,is:is,ts:te) )
6170!
6171!--    Get variable
6172          nc_stat = NF90_GET_VAR( id, id_var, tmp,                                &
6173                                  start = (/ ks+1, js+1, is+1, ts+1, ns /),           &
6174                                  count = (/ ke-ks+1, je-js+1, ie-is+1, te-ts+1, 1 /) )   
6175                               
6176          CALL handle_error( 'get_variable_5d_to_4d_real', 538, variable_name )
6177!
6178!--    Resort data. Please note, dimension subscripts of var all start at 1.
6179
6180          DO  t = ts, te 
6181             DO  i = is, ie 
6182                DO  j = js, je
6183                   DO  k = ks, ke
6184                      var(t-ts+1,i-is+1,j-js+1,k-ks+1) = tmp(k,j,i,t)
6185                   ENDDO
6186                ENDDO
6187             ENDDO
6188          ENDDO 
6189
6190          DEALLOCATE( tmp )
6191
6192       ENDIF
6193#endif
6194    END SUBROUTINE get_variable_5d_to_4d_real
6195
6196   
6197!------------------------------------------------------------------------------!
6198! Description:
6199! ------------
6200!> Reads a 5D float variable from file.
6201!> NOTE - This subroutine is used specific for reading NC variable
6202!>        emission_values having a "z" dimension.  Said dimension
6203!>        is to be removed in the future and this subroutine shall
6204!>        be depreciated accordingly (ecc 20190418)
6205!------------------------------------------------------------------------------!
6206    SUBROUTINE get_variable_5d_real( id, variable_name, var, is, ie, js, je,   &
6207                                     k1s, k1e, k2s, k2e, k3s, k3e )
6208
6209       USE indices
6210       USE pegrid
6211
6212       IMPLICIT NONE
6213
6214       CHARACTER(LEN=*)          ::  variable_name  !< variable name
6215
6216       INTEGER(iwp)              :: i       !< i index
6217       INTEGER(iwp)              :: ie      !< i index start
6218       INTEGER(iwp)              :: is      !< i index end
6219       INTEGER(iwp)              :: id_var  !< netCDF variable ID (varid)
6220       INTEGER(iwp)              :: j       !< j index
6221       INTEGER(iwp)              :: je      !< j index start
6222       INTEGER(iwp)              :: js      !< j index end
6223       INTEGER(iwp)              :: k1      !< k1 index
6224       INTEGER(iwp)              :: k1e     !< k1 index start
6225       INTEGER(iwp)              :: k1s     !< k1 index end
6226       INTEGER(iwp)              :: k2      !< k2 index
6227       INTEGER(iwp)              :: k2e     !< k2 index start
6228       INTEGER(iwp)              :: k2s     !< k2 index end
6229       INTEGER(iwp)              :: k3      !< k3 index
6230       INTEGER(iwp)              :: k3e     !< k3 index start
6231       INTEGER(iwp)              :: k3s     !< k3 index end
6232       INTEGER(iwp), INTENT(IN)  :: id      !< netCDF file ID (ncid)
6233
6234       REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE    :: tmp  !< temp array to read data from file
6235       REAL(wp), DIMENSION(:,:,:,:,:), INTENT(INOUT)  :: var  !< variable to be read
6236
6237#if defined( __netcdf )
6238
6239!
6240!-- Inquire variable id
6241
6242       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
6243
6244!
6245!-- Check for collective read-operation and set respective NetCDF flags if required.
6246 
6247       IF ( collective_read )  THEN
6248
6249#if defined( __netcdf4_parallel )       
6250          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
6251#endif
6252
6253       ENDIF
6254
6255!
6256!-- Allocate temporary variable according to memory access on file.
6257
6258       ALLOCATE( tmp(is:ie,js:je,k1s:k1e,k2s:k2e,k3s:k3e) )
6259
6260!
6261!-- Get variable from file
6262
6263       nc_stat = NF90_GET_VAR ( id, id_var, tmp,                                         &
6264                      start = (/ is+1,    js+1,    k1s+1,     k2s+1,     k3s+1 /),       &
6265                      count = (/ ie-is+1, je-js+1, k1e-k1s+1, k2e-k2s+1, k3e-k3s+1 /) )
6266
6267       CALL handle_error( 'get_variable_5d_real', 535, variable_name )
6268
6269!
6270!-- Resort (reverse index order) and standardize (from 1 to N) output array
6271
6272       DO  i = is, ie 
6273          DO  j = js, je
6274             DO  k1 = k1s, k1e
6275                DO  k2 = k2s, k2e
6276                   DO k3 = k3s, k3e
6277                      var(k3-k3s+1,k2-k2s+1,k1-k1s+1,j-js+1,i-is+1) = tmp(i,j,k1,k2,k3)
6278                   ENDDO
6279                ENDDO
6280             ENDDO
6281          ENDDO
6282       ENDDO
6283
6284       DEALLOCATE( tmp )
6285
6286#endif
6287
6288    END SUBROUTINE get_variable_5d_real
6289
6290
6291!------------------------------------------------------------------------------!
6292! Description:
6293! ------------
6294!> Reads a 5D float variables from dynamic driver, such as time-dependent xy-,
6295!> xz- or yz-boundary data as well as 5D initialization data. Please note,
6296!> the passed arguments are start indices and number of elements in each
6297!> dimension, which is in contrast to the other 3d versions where start- and
6298!> end indices are passed. The different handling of 5D dynamic variables is
6299!> due to its asymmetry for the u- and v component.
6300!> NOTE(1) - This subroutine is more flexible than get_variable_xd_real as it
6301!>           provides much better control over starting and count indices
6302!>           (ecc 20190418)
6303!> NOTE(2) - This subroutine is used specific for reading NC variable
6304!>           emission_values having a "z" dimension.  Said dimension
6305!>           is to be removed in the future and this subroutine shall
6306!>           be depreciated accordingly (ecc 20190418)
6307!------------------------------------------------------------------------------!
6308
6309    SUBROUTINE get_variable_5d_real_dynamic( id, variable_name, var,                       &
6310                                             i1s, i2s, i3s, i4s, i5s,                      &
6311                                             count_1, count_2, count_3, count_4, count_5,  &
6312                                             par_access )
6313
6314       USE indices
6315       USE pegrid
6316
6317       IMPLICIT NONE
6318
6319       CHARACTER(LEN=*)          ::  variable_name  !< variable name
6320
6321       LOGICAL                   ::  par_access     !< additional flag indicating parallel read
6322
6323       INTEGER(iwp)              ::  count_1  !< # elements read in dimension 1 wrt file
6324       INTEGER(iwp)              ::  count_2  !< # elements read in dimension 2 wrt file
6325       INTEGER(iwp)              ::  count_3  !< # elements read in dimension 3 wrt file
6326       INTEGER(iwp)              ::  count_4  !< # elements read in dimension 4 wrt file
6327       INTEGER(iwp)              ::  count_5  !< # elements read in dimension 5 wrt file
6328       INTEGER(iwp)              ::  i1       !< index for dimension 1 on file
6329       INTEGER(iwp)              ::  i1s      !< starting index for dimension 1 hyperslab
6330       INTEGER(iwp)              ::  i2       !< index for dimension 2 on file
6331       INTEGER(iwp)              ::  i2s      !< starting index for dimension 2 hyperslab
6332       INTEGER(iwp)              ::  i3       !< index for dimension 3 on file
6333       INTEGER(iwp)              ::  i3s      !< starting index for dimension 3 hyperslab
6334       INTEGER(iwp)              ::  i4       !< index for dimension 4 on file
6335       INTEGER(iwp)              ::  i4s      !< starting index for dimension 4 hyperslab
6336       INTEGER(iwp)              ::  i5       !< index for dimension 5 on file
6337       INTEGER(iwp)              ::  i5s      !< starting index for dimension 5 hyperslab
6338       INTEGER(iwp)              ::  id_var   !< netCDF variable id (varid)
6339       INTEGER(iwp)              ::  lb1      !< lower bound of dimension 1 wrt file
6340       INTEGER(iwp)              ::  lb2      !< lower bound of dimension 2 wrt file
6341       INTEGER(iwp)              ::  lb3      !< lower bound of dimension 3 wrt file
6342       INTEGER(iwp)              ::  lb4      !< lower bound of dimension 4 wrt file
6343       INTEGER(iwp)              ::  lb5      !< lower bound of dimension 5 wrt file
6344       INTEGER(iwp)              ::  ub1      !< upper bound of dimension 1 wrt file
6345       INTEGER(iwp)              ::  ub2      !< upper bound of dimension 2 wrt file
6346       INTEGER(iwp)              ::  ub3      !< upper bound of dimension 3 wrt file
6347       INTEGER(iwp)              ::  ub4      !< upper bound of dimension 4 wrt file
6348       INTEGER(iwp)              ::  ub5      !< upper bound of dimension 5 wrt file
6349       INTEGER(iwp), INTENT(IN)  ::  id       !< netCDF file id (ncid)
6350
6351       REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE    ::  tmp  !< temporary variable to read data
6352                                                               !< from file according is reverse
6353                                                               !< array index order
6354       REAL(wp), DIMENSION(:,:,:,:,:), INTENT(INOUT)  ::  var  !< input variable
6355       
6356#if defined( __netcdf )
6357
6358!
6359!-- Inquire variable id.
6360
6361       nc_stat = NF90_INQ_VARID( id, TRIM( variable_name ), id_var )
6362
6363!
6364!-- Check for collective read-operation and set respective NetCDF flags if required.
6365!-- Please note, in contrast to the other input routines where each PEs
6366!-- reads its subdomain data, dynamic input data not by all PEs, only
6367!-- by those which encompass lateral model boundaries. Hence, collective
6368!-- read operations are only enabled for top-boundary data.
6369
6370       IF ( collective_read  .AND.  par_access )  THEN
6371
6372#if defined( __netcdf4_parallel )       
6373          nc_stat = NF90_VAR_PAR_ACCESS (id, id_var, NF90_COLLECTIVE)
6374#endif
6375
6376       ENDIF
6377
6378!
6379!-- Allocate temporary variable according to memory access on file.
6380!-- Therefore, determine dimension bounds of input array.
6381
6382       lb1 = LBOUND(var,5)
6383       ub1 = UBOUND(var,5)
6384       lb2 = LBOUND(var,4)
6385       ub2 = UBOUND(var,4)
6386       lb3 = LBOUND(var,3)
6387       ub3 = UBOUND(var,3)
6388       lb4 = LBOUND(var,2)
6389       ub4 = UBOUND(var,2)
6390       lb5 = LBOUND(var,1)
6391       ub5 = UBOUND(var,1)
6392       ALLOCATE ( tmp(lb1:ub1,lb2:ub2,lb3:ub3,lb4:ub4,lb5:ub5) )
6393
6394!
6395!-- Get variable
6396
6397       nc_stat = NF90_GET_VAR(  id, id_var, tmp,                                         &
6398                      start = (/ i1s,     i2s,     i3s,     i4s,     i5s     /),         &
6399                      count = (/ count_1, count_2, count_3, count_4, count_5 /) )
6400
6401       CALL handle_error( 'get_variable_3d_real_dynamic', 537, variable_name )
6402
6403!
6404!-- Assign temp array to output.  Note reverse index order
6405
6406       DO  i5 = lb5, ub5
6407          DO  i4 = lb4, ub4
6408             DO  i3 = lb3, ub3
6409                DO i2 = lb2, ub2
6410                   DO  i1 = lb1, ub1
6411                      var(i5,i4,i3,i2,i1) = tmp(i1,i2,i3,i4,i5)
6412                   ENDDO
6413                ENDDO
6414             ENDDO
6415          ENDDO
6416       ENDDO
6417
6418       DEALLOCATE( tmp )
6419
6420#endif
6421
6422    END SUBROUTINE get_variable_5d_real_dynamic
6423
6424
6425!------------------------------------------------------------------------------!
6426! Description:
6427! ------------
6428!> Inquires the number of variables in a file
6429!------------------------------------------------------------------------------!
6430    SUBROUTINE inquire_num_variables( id, num_vars )
6431
6432       USE indices
6433       USE pegrid
6434
6435       IMPLICIT NONE
6436
6437       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
6438       INTEGER(iwp), INTENT(INOUT)   ::  num_vars        !< number of variables in a file
6439#if defined( __netcdf )
6440
6441       nc_stat = NF90_INQUIRE( id, NVARIABLES = num_vars )
6442       CALL handle_error( 'inquire_num_variables', 539 )
6443
6444#endif
6445    END SUBROUTINE inquire_num_variables
6446
6447
6448!------------------------------------------------------------------------------!
6449! Description:
6450! ------------
6451!> Inquires the variable names belonging to a file.
6452!------------------------------------------------------------------------------!
6453    SUBROUTINE inquire_variable_names( id, var_names )
6454
6455       USE indices
6456       USE pegrid
6457
6458       IMPLICIT NONE
6459
6460       CHARACTER(LEN=*), DIMENSION(:), INTENT(INOUT) ::  var_names   !< return variable - variable names
6461       INTEGER(iwp)                                  ::  i           !< loop variable
6462       INTEGER(iwp), INTENT(IN)                      ::  id          !< file id
6463       INTEGER(iwp)                                  ::  num_vars    !< number of variables (unused return parameter)
6464       INTEGER(iwp), DIMENSION(:), ALLOCATABLE       ::  varids      !< dummy array to strore variable ids temporarily
6465#if defined( __netcdf )
6466
6467       ALLOCATE( varids(1:SIZE(var_names)) )
6468       nc_stat = NF90_INQ_VARIDS( id, NVARS = num_vars, VARIDS = varids )
6469       CALL handle_error( 'inquire_variable_names', 540 )
6470
6471       DO  i = 1, SIZE(var_names)
6472          nc_stat = NF90_INQUIRE_VARIABLE( id, varids(i), NAME = var_names(i) )
6473          CALL handle_error( 'inquire_variable_names', 540 )
6474       ENDDO
6475
6476       DEALLOCATE( varids )
6477#endif
6478    END SUBROUTINE inquire_variable_names
6479
6480!------------------------------------------------------------------------------!
6481! Description:
6482! ------------
6483!> Prints out a text message corresponding to the current status.
6484!------------------------------------------------------------------------------!
6485    SUBROUTINE handle_error( routine_name, errno, name )
6486
6487       USE control_parameters,                                                 &
6488           ONLY:  message_string
6489
6490       IMPLICIT NONE
6491
6492       CHARACTER(LEN=6) ::  message_identifier !< string for the error number
6493       CHARACTER(LEN=*) ::  routine_name       !< routine name where the error happened
6494       CHARACTER(LEN=*), OPTIONAL ::  name     !< name of variable where reading failed
6495
6496       INTEGER(iwp) ::  errno
6497#if defined( __netcdf )
6498       
6499       IF ( nc_stat /= NF90_NOERR )  THEN
6500
6501          WRITE( message_identifier, '(''NC'',I4.4)' )  errno
6502         
6503          IF ( PRESENT( name ) )  THEN
6504             message_string = "Problem reading attribute/variable - " //       &
6505                              TRIM(name) // ": " //                            &
6506                              TRIM( NF90_STRERROR( nc_stat ) )
6507          ELSE
6508             message_string = TRIM( NF90_STRERROR( nc_stat ) )
6509          ENDIF
6510
6511          CALL message( routine_name, message_identifier, 2, 2, myid, 6, 1 )
6512
6513       ENDIF
6514
6515#endif
6516    END SUBROUTINE handle_error
6517
6518
6519 END MODULE netcdf_data_input_mod
Note: See TracBrowser for help on using the repository browser.