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

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

Bugfix, missing initialization of surface attributes in case of inifor-initialization branch

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