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

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

Nesting for chemical species implemented; Bugfix passive scalar boundary condition after anterpolation; Timeseries output of surface temperature; Enable initialization of 3D topography (was commented out so far)

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