source: palm/trunk/SOURCE/virtual_measurement_mod.f90 @ 4641

Last change on this file since 4641 was 4641, checked in by suehring, 4 years ago

Virtual measurement output: change content of attribute data_content, minor changes in long-name attributes and global attributes to be in agreement with (UC)2 data standard; driver creation config files: remove dummy input strings and change default values (to be in agreement with (UC)2 data standard); palm_csd_netcdf_interface: correct wrong false_easting attribute in crs variable

  • Property svn:executable set to *
  • Property svn:keywords set to Id
File size: 154.2 KB
Line 
1!> @virtual_measurement_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 terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: virtual_measurement_mod.f90 4641 2020-08-13 09:57:07Z suehring $
27! - To be in agreement with (UC)2 data standard do not list the measured variables in attribute
28!   data_content but simply set 'airmeteo'
29! - Bugfix in setting long_name attribute for variable t_va and for global attribute creation_time
30!
31! 4536 2020-05-17 17:24:13Z raasch
32! bugfix: preprocessor directive adjusted
33!
34! 4504 2020-04-20 12:11:24Z raasch
35! file re-formatted to follow the PALM coding standard
36!
37! 4481 2020-03-31 18:55:54Z maronga
38! bugfix: cpp-directives for serial mode added
39!
40! 4438 2020-03-03 20:49:28Z suehring
41! Add cpu-log points
42!
43! 4422 2020-02-24 22:45:13Z suehring
44! Missing trim()
45!
46! 4408 2020-02-14 10:04:39Z gronemeier
47! - Output of character string station_name after DOM has been enabled to
48!   output character variables
49! - Bugfix, missing coupling_char statement when opening the input file
50!
51! 4408 2020-02-14 10:04:39Z gronemeier
52! write fill_value attribute
53!
54! 4406 2020-02-13 20:06:29Z knoop
55! Bugix: removed oro_rel wrong loop bounds and removed unnecessary restart method
56!
57! 4400 2020-02-10 20:32:41Z suehring
58! Revision of the module:
59! - revised input from NetCDF setup file
60! - parallel NetCDF output via data-output module ( Tobias Gronemeier )
61! - variable attributes added
62! - further variables defined
63!
64! 4346 2019-12-18 11:55:56Z motisi
65! Introduction of wall_flags_total_0, which currently sets bits based on static
66! topography information used in wall_flags_static_0
67!
68! 4329 2019-12-10 15:46:36Z motisi
69! Renamed wall_flags_0 to wall_flags_static_0
70!
71! 4226 2019-09-10 17:03:24Z suehring
72! Netcdf input routine for dimension length renamed
73!
74! 4182 2019-08-22 15:20:23Z scharf
75! Corrected "Former revisions" section
76!
77! 4168 2019-08-16 13:50:17Z suehring
78! Replace function get_topography_top_index by topo_top_ind
79!
80! 3988 2019-05-22 11:32:37Z kanani
81! Add variables to enable steering of output interval for virtual measurements
82!
83! 3913 2019-04-17 15:12:28Z gronemeier
84! Bugfix: rotate positions of measurements before writing them into file
85!
86! 3910 2019-04-17 11:46:56Z suehring
87! Bugfix in rotation of UTM coordinates
88!
89! 3904 2019-04-16 18:22:51Z gronemeier
90! Rotate coordinates of stations by given rotation_angle
91!
92! 3876 2019-04-08 18:41:49Z knoop
93! Remove print statement
94!
95! 3854 2019-04-02 16:59:33Z suehring
96! renamed nvar to nmeas, replaced USE chem_modules by USE chem_gasphase_mod and
97! nspec by nvar
98!
99! 3766 2019-02-26 16:23:41Z raasch
100! unused variables removed
101!
102! 3718 2019-02-06 11:08:28Z suehring
103! Adjust variable name connections between UC2 and chemistry variables
104!
105! 3717 2019-02-05 17:21:16Z suehring
106! Additional check + error numbers adjusted
107!
108! 3706 2019-01-29 20:02:26Z suehring
109! unused variables removed
110!
111! 3705 2019-01-29 19:56:39Z suehring
112! - initialization revised
113! - binary data output
114! - list of allowed variables extended
115!
116! 3704 2019-01-29 19:51:41Z suehring
117! Sampling of variables
118!
119! 3473 2018-10-30 20:50:15Z suehring
120! Initial revision
121!
122! Authors:
123! --------
124! @author Matthias Suehring
125! @author Tobias Gronemeier
126!
127! Description:
128! ------------
129!> The module acts as an interface between 'real-world' observations and model simulations.
130!> Virtual measurements will be taken in the model at the coordinates representative for the
131!> 'real-world' observation coordinates. More precisely, coordinates and measured quanties will be
132!> read from a NetCDF file which contains all required information. In the model, the same
133!> quantities (as long as all the required components are switched-on) will be sampled at the
134!> respective positions and output into an extra file, which allows for straight-forward comparison
135!> of model results with observations.
136!--------------------------------------------------------------------------------------------------!
137 MODULE virtual_measurement_mod
138
139    USE arrays_3d,                                                                                 &
140        ONLY:  dzw,                                                                                &
141               exner,                                                                              &
142               hyp,                                                                                &
143               q,                                                                                  &
144               ql,                                                                                 &
145               pt,                                                                                 &
146               rho_air,                                                                            &
147               u,                                                                                  &
148               v,                                                                                  &
149               w,                                                                                  &
150               zu,                                                                                 &
151               zw
152
153    USE basic_constants_and_equations_mod,                                                         &
154        ONLY:  convert_utm_to_geographic,                                                          &
155               degc_to_k,                                                                          &
156               magnus,                                                                             &
157               pi,                                                                                 &
158               rd_d_rv
159
160    USE chem_gasphase_mod,                                                                         &
161        ONLY:  nvar
162
163    USE chem_modules,                                                                              &
164        ONLY:  chem_species
165
166    USE control_parameters,                                                                        &
167        ONLY:  air_chemistry,                                                                      &
168               coupling_char,                                                                      &
169               dz,                                                                                 &
170               end_time,                                                                           &
171               humidity,                                                                           &
172               message_string,                                                                     &
173               neutral,                                                                            &
174               origin_date_time,                                                                   &
175               rho_surface,                                                                        &
176               surface_pressure,                                                                   &
177               time_since_reference_point,                                                         &
178               virtual_measurement
179
180    USE cpulog,                                                                                    &
181        ONLY:  cpu_log,                                                                            &
182               log_point_s
183
184    USE data_output_module
185
186    USE grid_variables,                                                                            &
187        ONLY:  ddx,                                                                                &
188               ddy,                                                                                &
189               dx,                                                                                 &
190               dy
191
192    USE indices,                                                                                   &
193        ONLY:  nbgp,                                                                               &
194               nzb,                                                                                &
195               nzt,                                                                                &
196               nxl,                                                                                &
197               nxlg,                                                                               &
198               nxr,                                                                                &
199               nxrg,                                                                               &
200               nys,                                                                                &
201               nysg,                                                                               &
202               nyn,                                                                                &
203               nyng,                                                                               &
204               topo_top_ind,                                                                       &
205               wall_flags_total_0
206
207    USE kinds
208
209    USE netcdf_data_input_mod,                                                                     &
210        ONLY:  close_input_file,                                                                   &
211               coord_ref_sys,                                                                      &
212               crs_list,                                                                           &
213               get_attribute,                                                                      &
214               get_dimension_length,                                                               &
215               get_variable,                                                                       &
216               init_model,                                                                         &
217               input_file_atts,                                                                    &
218               input_file_vm,                                                                      &
219               input_pids_static,                                                                  &
220               input_pids_vm,                                                                      &
221               inquire_fill_value,                                                                 &
222               open_read_file,                                                                     &
223               pids_id
224
225    USE pegrid
226
227    USE surface_mod,                                                                               &
228        ONLY:  surf_lsm_h,                                                                         &
229               surf_usm_h
230
231    USE land_surface_model_mod,                                                                    &
232        ONLY:  m_soil_h,                                                                           &
233               nzb_soil,                                                                           &
234               nzt_soil,                                                                           &
235               t_soil_h,                                                                           &
236               zs
237
238    USE radiation_model_mod,                                                                       &
239        ONLY:  rad_lw_in,                                                                          &
240               rad_lw_out,                                                                         &
241               rad_sw_in,                                                                          &
242               rad_sw_in_diff,                                                                     &
243               rad_sw_out,                                                                         &
244               radiation_scheme
245
246    USE urban_surface_mod,                                                                         &
247        ONLY:  nzb_wall,                                                                           &
248               nzt_wall,                                                                           &
249               t_wall_h
250
251
252    IMPLICIT NONE
253
254    TYPE virt_general
255       INTEGER(iwp) ::  nvm = 0  !< number of virtual measurements
256    END TYPE virt_general
257
258    TYPE virt_var_atts
259       CHARACTER(LEN=100) ::  coordinates           !< defined longname of the variable
260       CHARACTER(LEN=100) ::  grid_mapping          !< defined longname of the variable
261       CHARACTER(LEN=100) ::  long_name             !< defined longname of the variable
262       CHARACTER(LEN=100) ::  name                  !< variable name
263       CHARACTER(LEN=100) ::  standard_name         !< defined standard name of the variable
264       CHARACTER(LEN=100) ::  units                 !< unit of the output variable
265
266       REAL(wp)           ::  fill_value = -9999.0  !< _FillValue attribute
267    END TYPE virt_var_atts
268
269    TYPE virt_mea
270       CHARACTER(LEN=100)  ::  feature_type                      !< type of the real-world measurement
271       CHARACTER(LEN=100)  ::  feature_type_out = 'timeSeries'   !< type of the virtual measurement
272                                                                 !< (all will be timeSeries, even trajectories)
273       CHARACTER(LEN=100)  ::  nc_filename                       !< name of the NetCDF output file for the station
274       CHARACTER(LEN=100)  ::  site                              !< name of the measurement site
275
276       CHARACTER(LEN=1000) ::  data_content = REPEAT(' ', 1000)  !< string of measured variables (data output only)
277
278       INTEGER(iwp) ::  end_coord_a     = 0  !< end coordinate in NetCDF file for local atmosphere observations
279       INTEGER(iwp) ::  end_coord_s     = 0  !< end coordinate in NetCDF file for local soil observations
280       INTEGER(iwp) ::  file_time_index = 0  !< time index in NetCDF output file
281       INTEGER(iwp) ::  ns              = 0  !< number of observation coordinates on subdomain, for atmospheric measurements
282       INTEGER(iwp) ::  ns_tot          = 0  !< total number of observation coordinates, for atmospheric measurements
283       INTEGER(iwp) ::  n_tr_st              !< number of trajectories / station of a measurement
284       INTEGER(iwp) ::  nmeas                !< number of measured variables (atmosphere + soil)
285       INTEGER(iwp) ::  ns_soil         = 0  !< number of observation coordinates on subdomain, for soil measurements
286       INTEGER(iwp) ::  ns_soil_tot     = 0  !< total number of observation coordinates, for soil measurements
287       INTEGER(iwp) ::  start_coord_a   = 0  !< start coordinate in NetCDF file for local atmosphere observations
288       INTEGER(iwp) ::  start_coord_s   = 0  !< start coordinate in NetCDF file for local soil observations
289
290       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  dim_t  !< number observations individual for each trajectory
291                                                          !< or station that are no _FillValues
292
293       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i       !< grid index for measurement position in x-direction
294       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j       !< grid index for measurement position in y-direction
295       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k       !< grid index for measurement position in k-direction
296
297       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i_soil  !< grid index for measurement position in x-direction
298       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  j_soil  !< grid index for measurement position in y-direction
299       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_soil  !< grid index for measurement position in k-direction
300
301       LOGICAL ::  soil_sampling      = .FALSE.  !< flag indicating that soil state variables were sampled
302       LOGICAL ::  trajectory         = .FALSE.  !< flag indicating that the observation is a mobile observation
303       LOGICAL ::  timseries          = .FALSE.  !< flag indicating that the observation is a stationary point measurement
304       LOGICAL ::  timseries_profile  = .FALSE.  !< flag indicating that the observation is a stationary profile measurement
305
306       REAL(wp) ::  fill_eutm          !< fill value for UTM coordinates in case of missing values
307       REAL(wp) ::  fill_nutm          !< fill value for UTM coordinates in case of missing values
308       REAL(wp) ::  fill_zar           !< fill value for heigth coordinates in case of missing values
309       REAL(wp) ::  fillout = -9999.0  !< fill value for output in case an observation is taken e.g. from inside a building
310       REAL(wp) ::  origin_x_obs       !< origin of the observation in UTM coordiates in x-direction
311       REAL(wp) ::  origin_y_obs       !< origin of the observation in UTM coordiates in y-direction
312
313       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  depth         !< measurement depth in soil
314       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  zar           !< measurement height above ground level
315
316       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  measured_vars       !< measured variables
317       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  measured_vars_soil  !< measured variables
318
319       TYPE( virt_var_atts ), DIMENSION(:), ALLOCATABLE ::  var_atts !< variable attributes
320    END TYPE virt_mea
321
322    CHARACTER(LEN=5)  ::  char_eutm = "E_UTM"            !< dimension name for UTM coordinate easting
323    CHARACTER(LEN=11) ::  char_feature = "featureType"   !< attribute name for feature type
324
325    ! This need to be generalized
326    CHARACTER(LEN=10) ::  char_fill = '_FillValue'                 !< attribute name for fill value
327    CHARACTER(LEN=9)  ::  char_long = 'long_name'                  !< attribute name for long_name
328    CHARACTER(LEN=18) ::  char_mv = "measured_variables"           !< variable name for the array with the measured variable names
329    CHARACTER(LEN=5)  ::  char_nutm = "N_UTM"                      !< dimension name for UTM coordinate northing
330    CHARACTER(LEN=18) ::  char_numstations = "number_of_stations"  !< attribute name for number of stations
331    CHARACTER(LEN=8)  ::  char_origx = "origin_x"                  !< attribute name for station coordinate in x
332    CHARACTER(LEN=8)  ::  char_origy = "origin_y"                  !< attribute name for station coordinate in y
333    CHARACTER(LEN=4)  ::  char_site = "site"                       !< attribute name for site name
334    CHARACTER(LEN=11) ::  char_soil = "soil_sample"                !< attribute name for soil sampling indication
335    CHARACTER(LEN=13) ::  char_standard = 'standard_name'          !< attribute name for standard_name
336    CHARACTER(LEN=9)  ::  char_station_h = "station_h"             !< variable name indicating height of the site
337    CHARACTER(LEN=5)  ::  char_unit = 'units'                      !< attribute name for standard_name
338    CHARACTER(LEN=1)  ::  char_zar = "z"                           !< attribute name indicating height above reference level
339    CHARACTER(LEN=10) ::  type_ts   = 'timeSeries'                 !< name of stationary point measurements
340    CHARACTER(LEN=10) ::  type_traj = 'trajectory'                 !< name of line measurements
341    CHARACTER(LEN=17) ::  type_tspr = 'timeSeriesProfile'          !< name of stationary profile measurements
342
343    CHARACTER(LEN=6), DIMENSION(1:5) ::  soil_vars = (/ 't_soil', & !< list of soil variables
344                                                        'm_soil',                                  &
345                                                        'lwc   ',                                  &
346                                                        'lwcs  ',                                  &
347                                                        'smp   ' /)
348
349    CHARACTER(LEN=10), DIMENSION(0:1,1:8) ::  chem_vars = RESHAPE( (/ 'mcpm1     ', 'PM1       ',  &
350                                                                      'mcpm2p5   ', 'PM2.5     ',  &
351                                                                      'mcpm10    ', 'PM10      ',  &
352                                                                      'mfno2     ', 'NO2       ',  &
353                                                                      'mfno      ', 'NO        ',  &
354                                                                      'mcno2     ', 'NO2       ',  &
355                                                                      'mcno      ', 'NO        ',  &
356                                                                      'tro3      ', 'O3        '   &
357                                                                    /), (/ 2, 8 /) )
358
359    INTEGER(iwp) ::  maximum_name_length = 32  !< maximum name length of station names
360    INTEGER(iwp) ::  ntimesteps                !< number of timesteps defined in NetCDF output file
361    INTEGER(iwp) ::  off_pr              = 1   !< number of neighboring grid points (in each direction) where virtual profile
362                                               !< measurements shall be taken, in addition to the given coordinates in the driver
363    INTEGER(iwp) ::  off_ts              = 1   !< number of neighboring grid points (in each direction) where virtual timeseries
364                                               !< measurements shall be taken, in addition to the given coordinates in the driver
365    INTEGER(iwp) ::  off_tr              = 1   !< number of neighboring grid points (in each direction) where virtual trajectory
366                                               !< measurements shall be taken, in addition to the given coordinates in the driver
367    LOGICAL ::  global_attribute          = .TRUE.   !< flag indicating a global attribute
368    LOGICAL ::  initial_write_coordinates = .FALSE.  !< flag indicating a global attribute
369    LOGICAL ::  use_virtual_measurement   = .FALSE.  !< Namelist parameter
370
371    REAL(wp) ::  dt_virtual_measurement   = 0.0_wp  !< sampling interval
372    REAL(wp) ::  time_virtual_measurement = 0.0_wp  !< time since last sampling
373    REAL(wp) ::  vm_time_start            = 0.0     !< time after which sampling shall start
374
375    TYPE( virt_general )                        ::  vmea_general  !< data structure which encompasses global variables
376    TYPE( virt_mea ), DIMENSION(:), ALLOCATABLE ::  vmea          !< data structure containing station-specific variables
377
378    INTERFACE vm_check_parameters
379       MODULE PROCEDURE vm_check_parameters
380    END INTERFACE vm_check_parameters
381
382    INTERFACE vm_data_output
383       MODULE PROCEDURE vm_data_output
384    END INTERFACE vm_data_output
385
386    INTERFACE vm_init
387       MODULE PROCEDURE vm_init
388    END INTERFACE vm_init
389
390    INTERFACE vm_init_output
391       MODULE PROCEDURE vm_init_output
392    END INTERFACE vm_init_output
393
394    INTERFACE vm_parin
395       MODULE PROCEDURE vm_parin
396    END INTERFACE vm_parin
397
398    INTERFACE vm_sampling
399       MODULE PROCEDURE vm_sampling
400    END INTERFACE vm_sampling
401
402    SAVE
403
404    PRIVATE
405
406!
407!-- Public interfaces
408    PUBLIC  vm_check_parameters,                                                                   &
409            vm_data_output,                                                                        &
410            vm_init,                                                                               &
411            vm_init_output,                                                                        &
412            vm_parin,                                                                              &
413            vm_sampling
414
415!
416!-- Public variables
417    PUBLIC  dt_virtual_measurement,                                                                &
418            time_virtual_measurement,                                                              &
419            vmea,                                                                                  &
420            vmea_general,                                                                          &
421            vm_time_start
422
423 CONTAINS
424
425
426!--------------------------------------------------------------------------------------------------!
427! Description:
428! ------------
429!> Check parameters for virtual measurement module
430!--------------------------------------------------------------------------------------------------!
431 SUBROUTINE vm_check_parameters
432
433    IF ( .NOT. virtual_measurement )  RETURN
434!
435!-- Virtual measurements require a setup file.
436    IF ( .NOT. input_pids_vm )  THEN
437       message_string = 'If virtual measurements are taken, a setup input ' //                     &
438                        'file for the site locations is mandatory.'
439       CALL message( 'vm_check_parameters', 'PA0533', 1, 2, 0, 6, 0 )
440    ENDIF
441!
442!-- In case virtual measurements are taken, a static input file is required.
443!-- This is because UTM coordinates for the PALM domain origin are required for correct mapping of
444!-- the measurements.
445!-- ToDo: Revise this later and remove this requirement.
446    IF ( .NOT. input_pids_static )  THEN
447       message_string = 'If virtual measurements are taken, a static input file is mandatory.'
448       CALL message( 'vm_check_parameters', 'PA0534', 1, 2, 0, 6, 0 )
449    ENDIF
450
451#if !defined( __netcdf4_parallel )
452!
453!-- In case of non-parallel NetCDF the virtual measurement output is not
454!-- working. This is only designed for parallel NetCDF.
455    message_string = 'If virtual measurements are taken, parallel NetCDF is required.'
456    CALL message( 'vm_check_parameters', 'PA0708', 1, 2, 0, 6, 0 )
457#endif
458!
459!-- Check if the given number of neighboring grid points do not exceed the number
460!-- of ghost points.
461    IF ( off_pr > nbgp - 1  .OR.  off_ts > nbgp - 1  .OR.  off_tr > nbgp - 1 )  THEN
462       WRITE(message_string,*)                                                                     &
463                        'If virtual measurements are taken, the number ' //                        &
464                        'of surrounding grid points must not be larger ' //                        &
465                        'than the number of ghost points - 1, which is: ', nbgp - 1
466       CALL message( 'vm_check_parameters', 'PA0705', 1, 2, 0, 6, 0 )
467    ENDIF
468
469    IF ( dt_virtual_measurement <= 0.0 )  THEN
470       message_string = 'dt_virtual_measurement must be > 0.0'
471       CALL message( 'check_parameters', 'PA0706', 1, 2, 0, 6, 0 )
472    ENDIF
473
474 END SUBROUTINE vm_check_parameters
475
476!--------------------------------------------------------------------------------------------------!
477! Description:
478! ------------
479!> Subroutine defines variable attributes according to UC2 standard. Note, later  this list can be
480!> moved to the data-output module where it can be re-used also for other output.
481!--------------------------------------------------------------------------------------------------!
482 SUBROUTINE vm_set_attributes( output_variable )
483
484    TYPE( virt_var_atts ), INTENT(INOUT) ::  output_variable !< data structure with attributes that need to be set
485
486    output_variable%long_name     = 'none'
487    output_variable%standard_name = 'none'
488    output_variable%units         = 'none'
489    output_variable%coordinates   = 'lon lat E_UTM N_UTM x y z time station_name'
490    output_variable%grid_mapping  = 'crs'
491
492    SELECT CASE ( TRIM( output_variable%name ) )
493
494       CASE ( 'u' )
495          output_variable%long_name     = 'u wind component'
496          output_variable%units         = 'm s-1'
497
498       CASE ( 'ua' )
499          output_variable%long_name     = 'eastward wind'
500          output_variable%standard_name = 'eastward_wind'
501          output_variable%units         = 'm s-1'
502
503       CASE ( 'v' )
504          output_variable%long_name     = 'v wind component'
505          output_variable%units         = 'm s-1'
506
507       CASE ( 'va' )
508          output_variable%long_name     = 'northward wind'
509          output_variable%standard_name = 'northward_wind'
510          output_variable%units         = 'm s-1'
511
512       CASE ( 'w' )
513          output_variable%long_name     = 'w wind component'
514          output_variable%standard_name = 'upward_air_velocity'
515          output_variable%units         = 'm s-1'
516
517       CASE ( 'wspeed' )
518          output_variable%long_name     = 'wind speed'
519          output_variable%standard_name = 'wind_speed'
520          output_variable%units         = 'm s-1'
521
522       CASE ( 'wdir' )
523          output_variable%long_name     = 'wind from direction'
524          output_variable%standard_name = 'wind_from_direction'
525          output_variable%units         = 'degrees'
526
527       CASE ( 'theta' )
528          output_variable%long_name     = 'air potential temperature'
529          output_variable%standard_name = 'air_potential_temperature'
530          output_variable%units         = 'K'
531
532       CASE ( 'utheta' )
533          output_variable%long_name     = 'eastward kinematic sensible heat flux in air'
534          output_variable%units         = 'K m s-1'
535
536       CASE ( 'vtheta' )
537          output_variable%long_name     = 'northward kinematic sensible heat flux in air'
538          output_variable%units         = 'K m s-1'
539
540       CASE ( 'wtheta' )
541          output_variable%long_name     = 'upward kinematic sensible heat flux in air'
542          output_variable%units         = 'K m s-1'
543
544       CASE ( 'ta' )
545          output_variable%long_name     = 'air temperature'
546          output_variable%standard_name = 'air_temperature'
547          output_variable%units         = 'degree_C'
548
549       CASE ( 't_va' )
550          output_variable%long_name     = 'virtual acoustic temperature'
551          output_variable%units         = 'K'
552
553       CASE ( 'haa' )
554          output_variable%long_name     = 'absolute atmospheric humidity'
555          output_variable%units         = 'kg m-3'
556
557       CASE ( 'hus' )
558          output_variable%long_name     = 'specific humidity'
559          output_variable%standard_name = 'specific_humidity'
560          output_variable%units         = 'kg kg-1'
561
562       CASE ( 'hur' )
563          output_variable%long_name     = 'relative humidity'
564          output_variable%standard_name = 'relative_humidity'
565          output_variable%units         = '1'
566
567       CASE ( 'rlu' )
568          output_variable%long_name     = 'upwelling longwave flux in air'
569          output_variable%standard_name = 'upwelling_longwave_flux_in_air'
570          output_variable%units         = 'W m-2'
571
572       CASE ( 'rlus' )
573          output_variable%long_name     = 'surface upwelling longwave flux in air'
574          output_variable%standard_name = 'surface_upwelling_longwave_flux_in_air'
575          output_variable%units         = 'W m-2'
576
577       CASE ( 'rld' )
578          output_variable%long_name     = 'downwelling longwave flux in air'
579          output_variable%standard_name = 'downwelling_longwave_flux_in_air'
580          output_variable%units         = 'W m-2'
581
582       CASE ( 'rsddif' )
583          output_variable%long_name     = 'diffuse downwelling shortwave flux in air'
584          output_variable%standard_name = 'diffuse_downwelling_shortwave_flux_in_air'
585          output_variable%units         = 'W m-2'
586
587       CASE ( 'rsd' )
588          output_variable%long_name     = 'downwelling shortwave flux in air'
589          output_variable%standard_name = 'downwelling_shortwave_flux_in_air'
590          output_variable%units         = 'W m-2'
591
592       CASE ( 'rnds' )
593          output_variable%long_name     = 'surface net downward radiative flux'
594          output_variable%standard_name = 'surface_net_downward_radiative_flux'
595          output_variable%units         = 'W m-2'
596
597       CASE ( 'rsu' )
598          output_variable%long_name     = 'upwelling shortwave flux in air'
599          output_variable%standard_name = 'upwelling_shortwave_flux_in_air'
600          output_variable%units         = 'W m-2'
601
602       CASE ( 'rsus' )
603          output_variable%long_name     = 'surface upwelling shortwave flux in air'
604          output_variable%standard_name = 'surface_upwelling_shortwave_flux_in_air'
605          output_variable%units         = 'W m-2'
606
607       CASE ( 'rsds' )
608          output_variable%long_name     = 'surface downwelling shortwave flux in air'
609          output_variable%standard_name = 'surface_downwelling_shortwave_flux_in_air'
610          output_variable%units         = 'W m-2'
611
612       CASE ( 'hfss' )
613          output_variable%long_name     = 'surface upward sensible heat flux'
614          output_variable%standard_name = 'surface_upward_sensible_heat_flux'
615          output_variable%units         = 'W m-2'
616
617       CASE ( 'hfls' )
618          output_variable%long_name     = 'surface upward latent heat flux'
619          output_variable%standard_name = 'surface_upward_latent_heat_flux'
620          output_variable%units         = 'W m-2'
621
622       CASE ( 'ts' )
623          output_variable%long_name     = 'surface temperature'
624          output_variable%standard_name = 'surface_temperature'
625          output_variable%units         = 'K'
626
627       CASE ( 'thetas' )
628          output_variable%long_name     = 'surface layer temperature scale'
629          output_variable%units         = 'K'
630
631       CASE ( 'us' )
632          output_variable%long_name     = 'friction velocity'
633          output_variable%units         = 'm s-1'
634
635       CASE ( 'uw' )
636          output_variable%long_name     = 'upward eastward kinematic momentum flux in air'
637          output_variable%units         = 'm2 s-2'
638
639       CASE ( 'vw' )
640          output_variable%long_name     = 'upward northward kinematic momentum flux in air'
641          output_variable%units         = 'm2 s-2'
642
643       CASE ( 'uv' )
644          output_variable%long_name     = 'eastward northward kinematic momentum flux in air'
645          output_variable%units         = 'm2 s-2'
646
647       CASE ( 'plev' )
648          output_variable%long_name     = 'air pressure'
649          output_variable%standard_name = 'air_pressure'
650          output_variable%units         = 'Pa'
651
652       CASE ( 'm_soil' )
653          output_variable%long_name     = 'soil moisture volumetric'
654          output_variable%units         = 'm3 m-3'
655
656       CASE ( 't_soil' )
657          output_variable%long_name     = 'soil temperature'
658          output_variable%standard_name = 'soil_temperature'
659          output_variable%units         = 'degree_C'
660
661       CASE ( 'hfdg' )
662          output_variable%long_name     = 'downward heat flux at ground level in soil'
663          output_variable%standard_name = 'downward_heat_flux_at_ground_level_in_soil'
664          output_variable%units         = 'W m-2'
665
666       CASE ( 'hfds' )
667          output_variable%long_name     = 'downward heat flux in soil'
668          output_variable%standard_name = 'downward_heat_flux_in_soil'
669          output_variable%units         = 'W m-2'
670
671       CASE ( 'hfla' )
672          output_variable%long_name     = 'upward latent heat flux in air'
673          output_variable%standard_name = 'upward_latent_heat_flux_in_air'
674          output_variable%units         = 'W m-2'
675
676       CASE ( 'hfsa' )
677          output_variable%long_name     = 'upward latent heat flux in air'
678          output_variable%standard_name = 'upward_sensible_heat_flux_in_air'
679          output_variable%units         = 'W m-2'
680
681       CASE ( 'jno2' )
682          output_variable%long_name     = 'photolysis rate of nitrogen dioxide'
683          output_variable%standard_name = 'photolysis_rate_of_nitrogen_dioxide'
684          output_variable%units         = 's-1'
685
686       CASE ( 'lwcs' )
687          output_variable%long_name     = 'liquid water content of soil layer'
688          output_variable%standard_name = 'liquid_water_content_of_soil_layer'
689          output_variable%units         = 'kg m-2'
690
691       CASE ( 'lwp' )
692          output_variable%long_name     = 'liquid water path'
693          output_variable%standard_name = 'atmosphere_mass_content_of_cloud_liquid_water'
694          output_variable%units         = 'kg m-2'
695
696       CASE ( 'ps' )
697          output_variable%long_name     = 'surface air pressure'
698          output_variable%standard_name = 'surface_air_pressure'
699          output_variable%units         = 'hPa'
700
701       CASE ( 'pswrtg' )
702          output_variable%long_name     = 'platform speed wrt ground'
703          output_variable%standard_name = 'platform_speed_wrt_ground'
704          output_variable%units         = 'm s-1'
705
706       CASE ( 'pswrta' )
707          output_variable%long_name     = 'platform speed wrt air'
708          output_variable%standard_name = 'platform_speed_wrt_air'
709          output_variable%units         = 'm s-1'
710
711       CASE ( 'pwv' )
712          output_variable%long_name     = 'water vapor partial pressure in air'
713          output_variable%standard_name = 'water_vapor_partial_pressure_in_air'
714          output_variable%units         = 'hPa'
715
716       CASE ( 'ssdu' )
717          output_variable%long_name     = 'duration of sunshine'
718          output_variable%standard_name = 'duration_of_sunshine'
719          output_variable%units         = 's'
720
721       CASE ( 't_lw' )
722          output_variable%long_name     = 'land water temperature'
723          output_variable%units         = 'degree_C'
724
725       CASE ( 'tb' )
726          output_variable%long_name     = 'brightness temperature'
727          output_variable%standard_name = 'brightness_temperature'
728          output_variable%units         = 'K'
729
730       CASE ( 'uqv' )
731          output_variable%long_name     = 'eastward kinematic latent heat flux in air'
732          output_variable%units         = 'g kg-1 m s-1'
733
734       CASE ( 'vqv' )
735          output_variable%long_name     = 'northward kinematic latent heat flux in air'
736          output_variable%units         = 'g kg-1 m s-1'
737
738       CASE ( 'wqv' )
739          output_variable%long_name     = 'upward kinematic latent heat flux in air'
740          output_variable%units         = 'g kg-1 m s-1'
741
742       CASE ( 'zcb' )
743          output_variable%long_name     = 'cloud base altitude'
744          output_variable%standard_name = 'cloud_base_altitude'
745          output_variable%units         = 'm'
746
747       CASE ( 'zmla' )
748          output_variable%long_name     = 'atmosphere boundary layer thickness'
749          output_variable%standard_name = 'atmosphere_boundary_layer_thickness'
750          output_variable%units         = 'm'
751
752       CASE ( 'mcpm1' )
753          output_variable%long_name     = 'mass concentration of pm1 ambient aerosol particles in air'
754          output_variable%standard_name = 'mass_concentration_of_pm1_ambient_aerosol_particles_in_air'
755          output_variable%units         = 'kg m-3'
756
757       CASE ( 'mcpm10' )
758          output_variable%long_name     = 'mass concentration of pm10 ambient aerosol particles in air'
759          output_variable%standard_name = 'mass_concentration_of_pm10_ambient_aerosol_particles_in_air'
760          output_variable%units         = 'kg m-3'
761
762       CASE ( 'mcpm2p5' )
763          output_variable%long_name     = 'mass concentration of pm2p5 ambient aerosol particles in air'
764          output_variable%standard_name = 'mass_concentration_of_pm2p5_ambient_aerosol_particles_in_air'
765          output_variable%units         = 'kg m-3'
766
767       CASE ( 'mfno', 'mcno'  )
768          output_variable%long_name     = 'mole fraction of nitrogen monoxide in air'
769          output_variable%standard_name = 'mole_fraction_of_nitrogen_monoxide_in_air'
770          output_variable%units         = 'ppm' !'mol mol-1'
771
772       CASE ( 'mfno2', 'mcno2'  )
773          output_variable%long_name     = 'mole fraction of nitrogen dioxide in air'
774          output_variable%standard_name = 'mole_fraction_of_nitrogen_dioxide_in_air'
775          output_variable%units         = 'ppm' !'mol mol-1'
776
777       CASE ( 'ncaa' )
778          output_variable%long_name     = 'number concentration of ambient aerosol particles in air'
779          output_variable%standard_name = 'number_concentration_of_ambient_aerosol_particles_in_air'
780          output_variable%units         = 'm-3' !'mol mol-1'
781
782       CASE ( 'tro3'  )
783          output_variable%long_name     = 'mole fraction of ozone in air'
784          output_variable%standard_name = 'mole_fraction_of_ozone_in_air'
785          output_variable%units         = 'ppm' !'mol mol-1'
786
787       CASE DEFAULT
788
789    END SELECT
790
791 END SUBROUTINE vm_set_attributes
792
793
794!--------------------------------------------------------------------------------------------------!
795! Description:
796! ------------
797!> Read namelist for the virtual measurement module
798!--------------------------------------------------------------------------------------------------!
799 SUBROUTINE vm_parin
800
801    CHARACTER(LEN=80) ::  line   !< dummy string that contains the current line of the parameter file
802
803    NAMELIST /virtual_measurement_parameters/  dt_virtual_measurement,                             &
804                                               off_ts,                                             &
805                                               off_pr,                                             &
806                                               off_tr,                                             &
807                                               use_virtual_measurement,                            &
808                                               vm_time_start
809
810    line = ' '
811!
812!-- Try to find stg package
813    REWIND ( 11 )
814    line = ' '
815    DO  WHILE ( INDEX( line, '&virtual_measurement_parameters' ) == 0 )
816       READ ( 11, '(A)', END=20 )  line
817    ENDDO
818    BACKSPACE ( 11 )
819
820!
821!-- Read namelist
822    READ ( 11, virtual_measurement_parameters, ERR = 10, END = 20 )
823
824!
825!-- Set flag that indicates that the virtual measurement module is switched on
826    IF ( use_virtual_measurement )  virtual_measurement = .TRUE.
827    GOTO 20
828
829 10 BACKSPACE( 11 )
830    READ( 11 , '(A)') line
831    CALL parin_fail_message( 'virtual_measurement_parameters', line )
832
833 20 CONTINUE
834
835 END SUBROUTINE vm_parin
836
837
838!--------------------------------------------------------------------------------------------------!
839! Description:
840! ------------
841!> Initialize virtual measurements: read coordiante arrays and measured variables, set indicies
842!> indicating the measurement points, read further attributes, etc..
843!--------------------------------------------------------------------------------------------------!
844 SUBROUTINE vm_init
845
846    CHARACTER(LEN=5)                  ::  dum                           !< dummy string indicating station id
847    CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables_file = ''  !< array with all measured variables read from NetCDF
848    CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables      = ''  !< dummy array with all measured variables that are allowed
849
850    INTEGER(iwp) ::  dim_ntime  !< dimension size of time coordinate
851    INTEGER(iwp) ::  i          !< grid index of virtual observation point in x-direction
852    INTEGER(iwp) ::  is         !< grid index of real observation point of the respective station in x-direction
853    INTEGER(iwp) ::  j          !< grid index of observation point in x-direction
854    INTEGER(iwp) ::  js         !< grid index of real observation point of the respective station in y-direction
855    INTEGER(iwp) ::  k          !< grid index of observation point in x-direction
856    INTEGER(iwp) ::  kl         !< lower vertical index of surrounding grid points of an observation coordinate
857    INTEGER(iwp) ::  ks         !< grid index of real observation point of the respective station in z-direction
858    INTEGER(iwp) ::  ksurf      !< topography top index
859    INTEGER(iwp) ::  ku         !< upper vertical index of surrounding grid points of an observation coordinate
860    INTEGER(iwp) ::  l          !< running index over all stations
861    INTEGER(iwp) ::  len_char   !< character length of single measured variables without Null character
862    INTEGER(iwp) ::  ll         !< running index over all measured variables in file
863    INTEGER(iwp) ::  m          !< running index for surface elements
864    INTEGER(iwp) ::  n          !< running index over trajectory coordinates
865    INTEGER(iwp) ::  nofill     !< dummy for nofill return value (not used)
866    INTEGER(iwp) ::  ns         !< counter variable for number of observation points on subdomain
867    INTEGER(iwp) ::  off        !< number of surrounding grid points to be sampled
868    INTEGER(iwp) ::  t          !< running index over number of trajectories
869
870    INTEGER(KIND=1)                             ::  soil_dum  !< dummy variable to input a soil flag
871
872    INTEGER(iwp), DIMENSION(:), ALLOCATABLE     ::  ns_all  !< dummy array used to sum-up the number of observation coordinates
873
874#if defined( __netcdf4_parallel )
875    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  ns_atmos  !< number of observation points for each station on each mpi rank
876    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  ns_soil   !< number of observation points for each station on each mpi rank
877#endif
878
879    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  meas_flag  !< mask array indicating measurement positions
880
881    LOGICAL  ::  on_pe  !< flag indicating that the respective measurement coordinate is on subdomain
882
883    REAL(wp) ::  fill_eutm !< _FillValue for coordinate array E_UTM
884    REAL(wp) ::  fill_nutm !< _FillValue for coordinate array N_UTM
885    REAL(wp) ::  fill_zar  !< _FillValue for height coordinate
886
887    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm      !< easting UTM coordinate, temporary variable
888    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm_tmp  !< EUTM coordinate before rotation
889    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm      !< northing UTM coordinate, temporary variable
890    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm_tmp  !< NUTM coordinate before rotation
891    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  station_h  !< station height above reference
892    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zar        !< observation height above reference
893#if defined( __netcdf )
894!
895!-- Open the input file.
896    CALL open_read_file( TRIM( input_file_vm ) // TRIM( coupling_char ), pids_id )
897!
898!-- Obtain number of sites.
899    CALL get_attribute( pids_id, char_numstations, vmea_general%nvm, global_attribute )
900!
901!-- Allocate data structure which encompasses all required information, such as  grid points indicies,
902!-- absolute UTM coordinates, the measured quantities, etc. .
903    ALLOCATE( vmea(1:vmea_general%nvm) )
904!
905!-- Allocate flag array. This dummy array is used to identify grid points where virtual measurements
906!-- should be taken. Please note, in order to include also the surrounding grid points of the
907!-- original coordinate, ghost points are required.
908    ALLOCATE( meas_flag(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
909    meas_flag = 0
910!
911!-- Loop over all sites in the setup file.
912    DO  l = 1, vmea_general%nvm
913!
914!--    Determine suffix which contains the ID, ordered according to the number of measurements.
915       IF( l < 10 )  THEN
916          WRITE( dum, '(I1)')  l
917       ELSEIF( l < 100 )  THEN
918          WRITE( dum, '(I2)')  l
919       ELSEIF( l < 1000 )  THEN
920          WRITE( dum, '(I3)')  l
921       ELSEIF( l < 10000 )  THEN
922          WRITE( dum, '(I4)')  l
923       ELSEIF( l < 100000 )  THEN
924          WRITE( dum, '(I5)')  l
925       ENDIF
926!
927!--    Read the origin site coordinates (UTM).
928       CALL get_attribute( pids_id, char_origx // TRIM( dum ), vmea(l)%origin_x_obs, global_attribute )
929       CALL get_attribute( pids_id, char_origy // TRIM( dum ), vmea(l)%origin_y_obs, global_attribute )
930!
931!--    Read site name.
932       CALL get_attribute( pids_id, char_site // TRIM( dum ), vmea(l)%site, global_attribute )
933!
934!--    Read a flag which indicates that also soil quantities are take at the respective site
935!--    (is part of the virtual measurement driver).
936       CALL get_attribute( pids_id, char_soil // TRIM( dum ), soil_dum, global_attribute )
937!
938!--    Set flag indicating soil-sampling.
939       IF ( soil_dum == 1 )  vmea(l)%soil_sampling = .TRUE.
940!
941!--    Read type of the measurement (trajectory, profile, timeseries).
942       CALL get_attribute( pids_id, char_feature // TRIM( dum ), vmea(l)%feature_type, global_attribute )
943!
944!---   Set logicals depending on the type of the measurement
945       IF ( INDEX( vmea(l)%feature_type, type_tspr     ) /= 0 )  THEN
946          vmea(l)%timseries_profile = .TRUE.
947       ELSEIF ( INDEX( vmea(l)%feature_type, type_ts   ) /= 0 )  THEN
948          vmea(l)%timseries         = .TRUE.
949       ELSEIF ( INDEX( vmea(l)%feature_type, type_traj ) /= 0 )  THEN
950          vmea(l)%trajectory        = .TRUE.
951!
952!--    Give error message in case the type matches non of the pre-defined types.
953       ELSE
954          message_string = 'Attribue featureType = ' // TRIM( vmea(l)%feature_type ) // ' is not allowed.'
955          CALL message( 'vm_init', 'PA0535', 1, 2, 0, 6, 0 )
956       ENDIF
957!
958!--    Read string with all measured variables at this site.
959       measured_variables_file = ''
960       CALL get_variable( pids_id, char_mv // TRIM( dum ), measured_variables_file )
961!
962!--    Count the number of measured variables.
963!--    Please note, for some NetCDF interal reasons, characters end with a NULL, i.e. also empty
964!--    characters contain a NULL. Therefore, check the strings for a NULL to get the correct
965!--    character length in order to compare them with the list of allowed variables.
966       vmea(l)%nmeas  = 1
967       DO  ll = 1, SIZE( measured_variables_file )
968          IF ( measured_variables_file(ll)(1:1) /= CHAR(0)  .AND.                                  &
969               measured_variables_file(ll)(1:1) /= ' ')  THEN
970!
971!--          Obtain character length of the character
972             len_char = 1
973             DO  WHILE ( measured_variables_file(ll)(len_char:len_char) /= CHAR(0)  .AND.          &
974                 measured_variables_file(ll)(len_char:len_char) /= ' ' )
975                len_char = len_char + 1
976             ENDDO
977             len_char = len_char - 1
978
979             measured_variables(vmea(l)%nmeas) = measured_variables_file(ll)(1:len_char)
980             vmea(l)%nmeas = vmea(l)%nmeas + 1
981
982          ENDIF
983       ENDDO
984       vmea(l)%nmeas = vmea(l)%nmeas - 1
985!
986!--    Allocate data-type array for the measured variables names and attributes at the respective
987!--    site.
988       ALLOCATE( vmea(l)%var_atts(1:vmea(l)%nmeas) )
989!
990!--    Store the variable names in a data structure, which assigns further attributes to this name.
991!--    Further, for data output reasons, create a string of output variables, which will be written
992!--    into the attribute data_content.
993       DO  ll = 1, vmea(l)%nmeas
994          vmea(l)%var_atts(ll)%name = TRIM( measured_variables(ll) )
995
996!           vmea(l)%data_content = TRIM( vmea(l)%data_content ) // " " //                            &
997!                                  TRIM( vmea(l)%var_atts(ll)%name )
998       ENDDO
999!
1000!--    Read all the UTM coordinates for the site. Based on the coordinates, define the grid-index
1001!--    space on each subdomain where virtual measurements should be taken. Note, the entire
1002!--    coordinate array (on the entire model domain) won't be stored as this would exceed memory
1003!--    requirements, particularly for trajectories.
1004       IF ( vmea(l)%nmeas > 0 )  THEN
1005!
1006!--       For stationary measurements UTM coordinates are just one value and its dimension is
1007!--       "station", while for mobile measurements UTM coordinates are arrays depending on the
1008!--       number of trajectories and time, according to (UC)2 standard. First, inquire dimension
1009!--       length of the UTM coordinates.
1010          IF ( vmea(l)%trajectory )  THEN
1011!
1012!--          For non-stationary measurements read the number of trajectories and the number of time
1013!--          coordinates.
1014             CALL get_dimension_length( pids_id, vmea(l)%n_tr_st, "traj" // TRIM( dum ) )
1015             CALL get_dimension_length( pids_id, dim_ntime, "ntime" // TRIM( dum ) )
1016!
1017!--       For stationary measurements the dimension for UTM is station and for the time-coordinate
1018!--       it is one.
1019          ELSE
1020             CALL get_dimension_length( pids_id, vmea(l)%n_tr_st, "station" // TRIM( dum ) )
1021             dim_ntime = 1
1022          ENDIF
1023!
1024!-        Allocate array which defines individual time/space frame for each trajectory or station.
1025          ALLOCATE( vmea(l)%dim_t(1:vmea(l)%n_tr_st) )
1026!
1027!--       Allocate temporary arrays for UTM and height coordinates. Note, on file UTM coordinates
1028!--       might be 1D or 2D variables
1029          ALLOCATE( e_utm(1:vmea(l)%n_tr_st,1:dim_ntime)       )
1030          ALLOCATE( n_utm(1:vmea(l)%n_tr_st,1:dim_ntime)       )
1031          ALLOCATE( station_h(1:vmea(l)%n_tr_st,1:dim_ntime)   )
1032          ALLOCATE( zar(1:vmea(l)%n_tr_st,1:dim_ntime)         )
1033          e_utm     = 0.0_wp
1034          n_utm     = 0.0_wp
1035          station_h = 0.0_wp
1036          zar       = 0.0_wp
1037
1038          ALLOCATE( e_utm_tmp(1:vmea(l)%n_tr_st,1:dim_ntime) )
1039          ALLOCATE( n_utm_tmp(1:vmea(l)%n_tr_st,1:dim_ntime) )
1040!
1041!--       Read UTM and height coordinates for all trajectories and times. Note, in case
1042!--       these obtain any missing values, replace them with default _FillValues.
1043          CALL inquire_fill_value( pids_id, char_eutm // TRIM( dum ), nofill, fill_eutm )
1044          CALL inquire_fill_value( pids_id, char_nutm // TRIM( dum ), nofill, fill_nutm )
1045          CALL inquire_fill_value( pids_id, char_zar // TRIM( dum ), nofill, fill_zar )
1046!
1047!--       Further line is just to avoid compiler warnings. nofill might be used in future.
1048          IF ( nofill == 0  .OR.  nofill /= 0 )  CONTINUE
1049!
1050!--       Read observation coordinates. Please note, for trajectories the observation height is
1051!--       stored directly in z, while for timeSeries it is stored in z - station_h, according to
1052!--       UC2-standard.
1053          IF ( vmea(l)%trajectory )  THEN
1054             CALL get_variable( pids_id, char_eutm // TRIM( dum ), e_utm, 0, dim_ntime-1, 0,       &
1055                                vmea(l)%n_tr_st-1 )
1056             CALL get_variable( pids_id, char_nutm // TRIM( dum ), n_utm, 0, dim_ntime-1, 0,       &
1057                                vmea(l)%n_tr_st-1 )
1058             CALL get_variable( pids_id, char_zar // TRIM( dum ), zar, 0, dim_ntime-1, 0,          &
1059                                vmea(l)%n_tr_st-1 )
1060          ELSE
1061             CALL get_variable( pids_id, char_eutm // TRIM( dum ), e_utm(:,1) )
1062             CALL get_variable( pids_id, char_nutm // TRIM( dum ), n_utm(:,1) )
1063             CALL get_variable( pids_id, char_station_h // TRIM( dum ), station_h(:,1) )
1064             CALL get_variable( pids_id, char_zar // TRIM( dum ), zar(:,1) )
1065          ENDIF
1066
1067          e_utm = MERGE( e_utm, vmea(l)%fillout, e_utm /= fill_eutm )
1068          n_utm = MERGE( n_utm, vmea(l)%fillout, n_utm /= fill_nutm )
1069          zar   = MERGE( zar,   vmea(l)%fillout, zar   /= fill_zar  )
1070!
1071!--       Compute observation height above ground.
1072          zar  = zar - station_h
1073!
1074!--       Based on UTM coordinates, check if the measurement station or parts of the trajectory are
1075!--       on subdomain. This case, setup grid index space sample these quantities.
1076          meas_flag = 0
1077          DO  t = 1, vmea(l)%n_tr_st
1078!
1079!--          First, compute relative x- and y-coordinates with respect to the lower-left origin of
1080!--          the model domain, which is the difference between UTM coordinates. Note, if the origin
1081!--          is not correct, the virtual sites will be misplaced. Further, in case of an rotated
1082!--          model domain, the UTM coordinates must also be rotated.
1083             e_utm_tmp(t,1:dim_ntime) = e_utm(t,1:dim_ntime) - init_model%origin_x
1084             n_utm_tmp(t,1:dim_ntime) = n_utm(t,1:dim_ntime) - init_model%origin_y
1085             e_utm(t,1:dim_ntime) = COS( init_model%rotation_angle * pi / 180.0_wp )               &
1086                                    * e_utm_tmp(t,1:dim_ntime)                                     &
1087                                  - SIN( init_model%rotation_angle * pi / 180.0_wp )               &
1088                                    * n_utm_tmp(t,1:dim_ntime)
1089             n_utm(t,1:dim_ntime) = SIN( init_model%rotation_angle * pi / 180.0_wp )               &
1090                                    * e_utm_tmp(t,1:dim_ntime)                                     &
1091                                  + COS( init_model%rotation_angle * pi / 180.0_wp )               &
1092                                    * n_utm_tmp(t,1:dim_ntime)
1093!
1094!--          Determine the individual time coordinate length for each station and trajectory. This
1095!--          is required as several stations and trajectories are merged into one file but they do
1096!--          not have the same number of points in time, hence, missing values may occur and cannot
1097!--          be processed further. This is actually a work-around for the specific (UC)2 dataset,
1098!--          but it won't harm anyway.
1099             vmea(l)%dim_t(t) = 0
1100             DO  n = 1, dim_ntime
1101                IF ( e_utm(t,n) /= fill_eutm  .AND.  n_utm(t,n) /= fill_nutm  .AND.                &
1102                     zar(t,n)   /= fill_zar )  vmea(l)%dim_t(t) = n
1103             ENDDO
1104!
1105!--          Compute grid indices relative to origin and check if these are on the subdomain. Note,
1106!--          virtual measurements will be taken also at grid points surrounding the station, hence,
1107!--          check also for these grid points. The number of surrounding grid points is set
1108!--          according to the featureType.
1109             IF ( vmea(l)%timseries_profile )  THEN
1110                off = off_pr
1111             ELSEIF ( vmea(l)%timseries     )  THEN
1112                off = off_ts
1113             ELSEIF ( vmea(l)%trajectory    )  THEN
1114                off = off_tr
1115             ENDIF
1116
1117             DO  n = 1, vmea(l)%dim_t(t)
1118                 is = INT( ( e_utm(t,n) + 0.5_wp * dx ) * ddx, KIND = iwp )
1119                 js = INT( ( n_utm(t,n) + 0.5_wp * dy ) * ddy, KIND = iwp )
1120!
1121!--             Is the observation point on subdomain?
1122                on_pe = ( is >= nxl  .AND.  is <= nxr  .AND.  js >= nys  .AND.  js <= nyn )
1123!
1124!--             Check if observation coordinate is on subdomain.
1125                IF ( on_pe )  THEN
1126!
1127!--                Determine vertical index which corresponds to the observation height.
1128                   ksurf = topo_top_ind(js,is,0)
1129                   ks = MINLOC( ABS( zu - zw(ksurf) - zar(t,n) ), DIM = 1 ) - 1
1130!
1131!--                Set mask array at the observation coordinates. Also, flag the surrounding
1132!--                coordinate points, but first check whether the surrounding coordinate points are
1133!--                on the subdomain.
1134                   kl = MERGE( ks-off, ksurf, ks-off >= nzb  .AND. ks-off >= ksurf )
1135                   ku = MERGE( ks+off, nzt,   ks+off < nzt+1 )
1136
1137                   DO  i = is-off, is+off
1138                      DO  j = js-off, js+off
1139                         DO  k = kl, ku
1140                            meas_flag(k,j,i) = MERGE( IBSET( meas_flag(k,j,i), 0 ), 0,             &
1141                                               BTEST( wall_flags_total_0(k,j,i), 0 ) )
1142                         ENDDO
1143                      ENDDO
1144                   ENDDO
1145                ENDIF
1146             ENDDO
1147
1148          ENDDO
1149!
1150!--       Based on the flag array, count the number of sampling coordinates. Please note, sampling
1151!--       coordinates in atmosphere and soil may be different, as within the soil all levels will be
1152!--       measured. Hence, count individually. Start with atmoshere.
1153          ns = 0
1154          DO  i = nxl-off, nxr+off
1155             DO  j = nys-off, nyn+off
1156                DO  k = nzb, nzt+1
1157                   ns = ns + MERGE( 1, 0, BTEST( meas_flag(k,j,i), 0 ) )
1158                ENDDO
1159             ENDDO
1160          ENDDO
1161
1162!
1163!--       Store number of observation points on subdomain and allocate index arrays as well as array
1164!--       containing height information.
1165          vmea(l)%ns = ns
1166
1167          ALLOCATE( vmea(l)%i(1:vmea(l)%ns) )
1168          ALLOCATE( vmea(l)%j(1:vmea(l)%ns) )
1169          ALLOCATE( vmea(l)%k(1:vmea(l)%ns) )
1170          ALLOCATE( vmea(l)%zar(1:vmea(l)%ns) )
1171!
1172!--       Based on the flag array store the grid indices which correspond to the observation
1173!--       coordinates.
1174          ns = 0
1175          DO  i = nxl-off, nxr+off
1176             DO  j = nys-off, nyn+off
1177                DO  k = nzb, nzt+1
1178                   IF ( BTEST( meas_flag(k,j,i), 0 ) )  THEN
1179                      ns = ns + 1
1180                      vmea(l)%i(ns) = i
1181                      vmea(l)%j(ns) = j
1182                      vmea(l)%k(ns) = k
1183                      vmea(l)%zar(ns)  = zu(k) - zw(topo_top_ind(j,i,0))
1184                   ENDIF
1185                ENDDO
1186             ENDDO
1187          ENDDO
1188!
1189!--       Same for the soil. Based on the flag array, count the number of sampling coordinates in
1190!--       soil. Sample at all soil levels in this case. Please note, soil variables can only be
1191!--       sampled on subdomains, not on ghost layers.
1192          IF ( vmea(l)%soil_sampling )  THEN
1193             DO  i = nxl, nxr
1194                DO  j = nys, nyn
1195                   IF ( ANY( BTEST( meas_flag(:,j,i), 0 ) ) )  THEN
1196                      IF ( surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i) )  THEN
1197                         vmea(l)%ns_soil = vmea(l)%ns_soil + nzt_soil - nzb_soil + 1
1198                      ENDIF
1199                      IF ( surf_usm_h%start_index(j,i) <= surf_usm_h%end_index(j,i) )  THEN
1200                         vmea(l)%ns_soil = vmea(l)%ns_soil + nzt_wall - nzb_wall + 1
1201                      ENDIF
1202                   ENDIF
1203                ENDDO
1204             ENDDO
1205          ENDIF
1206!
1207!--       Allocate index arrays as well as array containing height information for soil.
1208          IF ( vmea(l)%soil_sampling )  THEN
1209             ALLOCATE( vmea(l)%i_soil(1:vmea(l)%ns_soil) )
1210             ALLOCATE( vmea(l)%j_soil(1:vmea(l)%ns_soil) )
1211             ALLOCATE( vmea(l)%k_soil(1:vmea(l)%ns_soil) )
1212             ALLOCATE( vmea(l)%depth(1:vmea(l)%ns_soil)  )
1213          ENDIF
1214!
1215!--       For soil, store the grid indices.
1216          ns = 0
1217          IF ( vmea(l)%soil_sampling )  THEN
1218             DO  i = nxl, nxr
1219                DO  j = nys, nyn
1220                   IF ( ANY( BTEST( meas_flag(:,j,i), 0 ) ) )  THEN
1221                      IF ( surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i) )  THEN
1222                         m = surf_lsm_h%start_index(j,i)
1223                         DO  k = nzb_soil, nzt_soil
1224                            ns = ns + 1
1225                            vmea(l)%i_soil(ns) = i
1226                            vmea(l)%j_soil(ns) = j
1227                            vmea(l)%k_soil(ns) = k
1228                            vmea(l)%depth(ns)  = - zs(k)
1229                         ENDDO
1230                      ENDIF
1231
1232                      IF ( surf_usm_h%start_index(j,i) <= surf_usm_h%end_index(j,i) )  THEN
1233                         m = surf_usm_h%start_index(j,i)
1234                         DO  k = nzb_wall, nzt_wall
1235                            ns = ns + 1
1236                            vmea(l)%i_soil(ns) = i
1237                            vmea(l)%j_soil(ns) = j
1238                            vmea(l)%k_soil(ns) = k
1239                            vmea(l)%depth(ns)  = - surf_usm_h%zw(k,m)
1240                         ENDDO
1241                      ENDIF
1242                   ENDIF
1243                ENDDO
1244             ENDDO
1245          ENDIF
1246!
1247!--       Allocate array to save the sampled values.
1248          ALLOCATE( vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nmeas) )
1249
1250          IF ( vmea(l)%soil_sampling )                                                             &
1251             ALLOCATE( vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil, 1:vmea(l)%nmeas) )
1252!
1253!--       Initialize with _FillValues
1254          vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nmeas) = vmea(l)%fillout
1255          IF ( vmea(l)%soil_sampling )                                                             &
1256             vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil,1:vmea(l)%nmeas) = vmea(l)%fillout
1257!
1258!--       Deallocate temporary coordinate arrays
1259          IF ( ALLOCATED( e_utm )     )  DEALLOCATE( e_utm )
1260          IF ( ALLOCATED( n_utm )     )  DEALLOCATE( n_utm )
1261          IF ( ALLOCATED( e_utm_tmp ) )  DEALLOCATE( e_utm_tmp )
1262          IF ( ALLOCATED( n_utm_tmp ) )  DEALLOCATE( n_utm_tmp )
1263          IF ( ALLOCATED( n_utm )     )  DEALLOCATE( n_utm )
1264          IF ( ALLOCATED( zar  )      )  DEALLOCATE( vmea(l)%dim_t )
1265          IF ( ALLOCATED( zar  )      )  DEALLOCATE( zar  )
1266          IF ( ALLOCATED( station_h ) )  DEALLOCATE( station_h )
1267
1268       ENDIF
1269    ENDDO
1270!
1271!-- Dellocate flag array
1272    DEALLOCATE( meas_flag )
1273!
1274!-- Close input file for virtual measurements.
1275    CALL close_input_file( pids_id )
1276!
1277!-- Sum-up the number of observation coordiates, for atmosphere first.
1278!-- This is actually only required for data output.
1279    ALLOCATE( ns_all(1:vmea_general%nvm) )
1280    ns_all = 0
1281#if defined( __parallel )
1282    CALL MPI_ALLREDUCE( vmea(:)%ns, ns_all(:), vmea_general%nvm,                                   &
1283                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
1284#else
1285    ns_all(:) = vmea(:)%ns
1286#endif
1287    vmea(:)%ns_tot = ns_all(:)
1288!
1289!-- Now for soil
1290    ns_all = 0
1291#if defined( __parallel )
1292    CALL MPI_ALLREDUCE( vmea(:)%ns_soil, ns_all(:), vmea_general%nvm,                              &
1293                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
1294#else
1295    ns_all(:) = vmea(:)%ns_soil
1296#endif
1297    vmea(:)%ns_soil_tot = ns_all(:)
1298
1299    DEALLOCATE( ns_all )
1300!
1301!-- In case of parallel NetCDF the start coordinate for each mpi rank needs to be defined, so that
1302!-- each processor knows where to write the data.
1303#if defined( __netcdf4_parallel )
1304    ALLOCATE( ns_atmos(0:numprocs-1,1:vmea_general%nvm) )
1305    ALLOCATE( ns_soil(0:numprocs-1,1:vmea_general%nvm)  )
1306    ns_atmos = 0
1307    ns_soil  = 0
1308
1309    DO  l = 1, vmea_general%nvm
1310       ns_atmos(myid,l) = vmea(l)%ns
1311       ns_soil(myid,l)  = vmea(l)%ns_soil
1312    ENDDO
1313
1314#if defined( __parallel )
1315    CALL MPI_ALLREDUCE( MPI_IN_PLACE, ns_atmos, numprocs * vmea_general%nvm,                       &
1316                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
1317    CALL MPI_ALLREDUCE( MPI_IN_PLACE, ns_soil, numprocs * vmea_general%nvm,                        &
1318                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
1319#else
1320    ns_atmos(0,:) = vmea(:)%ns
1321    ns_soil(0,:)  = vmea(:)%ns_soil
1322#endif
1323
1324!
1325!-- Determine the start coordinate in NetCDF file for the local arrays. Note, start coordinates are
1326!-- initialized with zero for sake of simplicity in summation. However, in NetCDF the start
1327!-- coordinates must be >= 1, so that a one needs to be added at the end.
1328    DO  l = 1, vmea_general%nvm
1329       DO  n  = 0, myid - 1
1330          vmea(l)%start_coord_a = vmea(l)%start_coord_a + ns_atmos(n,l)
1331          vmea(l)%start_coord_s = vmea(l)%start_coord_s + ns_soil(n,l)
1332       ENDDO
1333!
1334!--    Start coordinate in NetCDF starts always at one not at 0.
1335       vmea(l)%start_coord_a = vmea(l)%start_coord_a + 1
1336       vmea(l)%start_coord_s = vmea(l)%start_coord_s + 1
1337!
1338!--    Determine the local end coordinate
1339       vmea(l)%end_coord_a = vmea(l)%start_coord_a + vmea(l)%ns - 1
1340       vmea(l)%end_coord_s = vmea(l)%start_coord_s + vmea(l)%ns_soil - 1
1341    ENDDO
1342
1343    DEALLOCATE( ns_atmos )
1344    DEALLOCATE( ns_soil  )
1345
1346#endif
1347
1348#endif
1349
1350 END SUBROUTINE vm_init
1351
1352
1353!--------------------------------------------------------------------------------------------------!
1354! Description:
1355! ------------
1356!> Initialize output using data-output module
1357!--------------------------------------------------------------------------------------------------!
1358 SUBROUTINE vm_init_output
1359
1360    CHARACTER(LEN=100) ::  variable_name  !< name of output variable
1361
1362    INTEGER(iwp) ::  l             !< loop index
1363    INTEGER(iwp) ::  n             !< loop index
1364    INTEGER      ::  return_value  !< returned status value of called function
1365
1366    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ndim !< dummy to write dimension
1367
1368    REAL(wp) ::  dum_lat  !< transformed geographical coordinate (latitude)
1369    REAL(wp) ::  dum_lon  !< transformed geographical coordinate (longitude)
1370
1371!
1372!-- Determine the number of output timesteps.
1373    ntimesteps = CEILING( ( end_time - MAX( vm_time_start, time_since_reference_point )            &
1374                          ) / dt_virtual_measurement )
1375!
1376!-- Create directory where output files will be stored.
1377    CALL local_system( 'mkdir -p VM_OUTPUT' // TRIM( coupling_char ) )
1378!
1379!-- Loop over all sites.
1380    DO  l = 1, vmea_general%nvm
1381!
1382!--    Skip if no observations will be taken for this site.
1383       IF ( vmea(l)%ns_tot == 0  .AND.  vmea(l)%ns_soil_tot == 0 )  CYCLE
1384!
1385!--    Define output file.
1386       WRITE( vmea(l)%nc_filename, '(A,I4.4)' ) 'VM_OUTPUT' // TRIM( coupling_char ) // '/' //     &
1387              'site', l
1388
1389       return_value = dom_def_file( vmea(l)%nc_filename, 'netcdf4-parallel' )
1390!
1391!--    Define global attributes.
1392!--    Before, transform UTM into geographical coordinates.
1393       CALL convert_utm_to_geographic( crs_list, vmea(l)%origin_x_obs, vmea(l)%origin_y_obs,       &
1394                                       dum_lon, dum_lat )
1395
1396       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'site',                   &
1397                                   value = TRIM( vmea(l)%site ) )
1398       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'title',                  &
1399                                   value = 'Virtual measurement output')
1400       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'source',                 &
1401                                   value = 'PALM-4U')
1402       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'institution',            &
1403                                   value = input_file_atts%institution )
1404       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'acronym',                &
1405                                   value = input_file_atts%acronym )
1406       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'author',                 &
1407                                   value = input_file_atts%author )
1408       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'contact_person',         &
1409                                   value = input_file_atts%author )
1410       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'iop',                    &
1411                                   value = input_file_atts%campaign )
1412       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'campaign',               &
1413                                   value = 'PALM-4U' )
1414       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'origin_time ',           &
1415                                   value = origin_date_time)
1416       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'location',               &
1417                                   value = input_file_atts%location )
1418       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'origin_x',               &
1419                                   value = vmea(l)%origin_x_obs )
1420       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'origin_y',               &
1421                                   value = vmea(l)%origin_y_obs )
1422       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'origin_lon',             &
1423                                   value = dum_lon )
1424       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'origin_lat',             &
1425                                   value = dum_lat )
1426       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'origin_z', value = 0.0 )
1427       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'rotation_angle',         &
1428                                   value = input_file_atts%rotation_angle )
1429       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'featureType',            &
1430                                   value = TRIM( vmea(l)%feature_type_out ) )
1431       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'data_content',           &
1432                                   value = TRIM( vmea(l)%data_content ) )
1433       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'creation_time',          &
1434                                   value = input_file_atts%creation_time )
1435       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'version', value = 1 ) !input_file_atts%version
1436       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'Conventions',            &
1437                                   value = input_file_atts%conventions )
1438       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'dependencies',           &
1439                                   value = input_file_atts%dependencies )
1440       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'history',                &
1441                                   value = input_file_atts%history )
1442       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'references',             &
1443                                   value = input_file_atts%references )
1444       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'comment',                &
1445                                   value = input_file_atts%comment )
1446       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'keywords',               &
1447                                   value = input_file_atts%keywords )
1448       return_value = dom_def_att( vmea(l)%nc_filename, attribute_name = 'licence',                &
1449                                   value = '[UC]2 Open Licence; see [UC]2 ' //                     &
1450                                           'data policy available at ' //                          &
1451                                           'www.uc2-program.org/uc2_data_policy.pdf' )
1452!
1453!--    Define dimensions.
1454!--    station
1455       ALLOCATE( ndim(1:vmea(l)%ns_tot) )
1456       DO  n = 1, vmea(l)%ns_tot
1457          ndim(n) = n
1458       ENDDO
1459       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'station',                &
1460                                   output_type = 'int32', bounds = (/1_iwp, vmea(l)%ns_tot/),      &
1461                                   values_int32 = ndim )
1462       DEALLOCATE( ndim )
1463!
1464!--    ntime
1465       ALLOCATE( ndim(1:ntimesteps) )
1466       DO  n = 1, ntimesteps
1467          ndim(n) = n
1468       ENDDO
1469
1470       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'ntime',                  &
1471                                   output_type = 'int32', bounds = (/1_iwp, ntimesteps/),          &
1472                                   values_int32 = ndim )
1473       DEALLOCATE( ndim )
1474!
1475!--    nv
1476       ALLOCATE( ndim(1:2) )
1477       DO  n = 1, 2
1478          ndim(n) = n
1479       ENDDO
1480
1481       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'nv',                     &
1482                                   output_type = 'int32', bounds = (/1_iwp, 2_iwp/),               &
1483                                   values_int32 = ndim )
1484       DEALLOCATE( ndim )
1485!
1486!--    maximum name length
1487       ALLOCATE( ndim(1:maximum_name_length) )
1488       DO  n = 1, maximum_name_length
1489          ndim(n) = n
1490       ENDDO
1491
1492       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'max_name_len',           &
1493                                   output_type = 'int32',                                          &
1494                                   bounds = (/1_iwp, maximum_name_length /), values_int32 = ndim )
1495       DEALLOCATE( ndim )
1496!
1497!--    Define coordinate variables.
1498!--    time
1499       variable_name = 'time'
1500       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1501                                   dimension_names = (/ 'station  ', 'ntime    '/),                &
1502                                   output_type = 'real32' )
1503!
1504!--    station_name
1505       variable_name = 'station_name'
1506       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1507                                   dimension_names = (/ 'max_name_len', 'station     ' /),         &
1508                                   output_type = 'char' )
1509!
1510!--    vrs (vertical reference system)
1511       variable_name = 'vrs'
1512       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1513                                   dimension_names = (/ 'station' /), output_type = 'int8' )
1514!
1515!--    crs (coordinate reference system)
1516       variable_name = 'crs'
1517       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1518                                   dimension_names = (/ 'station' /), output_type = 'int8' )
1519!
1520!--    z
1521       variable_name = 'z'
1522       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1523                                   dimension_names = (/'station'/), output_type = 'real32' )
1524!
1525!--    station_h
1526       variable_name = 'station_h'
1527       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1528                                   dimension_names = (/'station'/), output_type = 'real32' )
1529!
1530!--    x
1531       variable_name = 'x'
1532       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1533                                   dimension_names = (/'station'/), output_type = 'real32' )
1534!
1535!--    y
1536       variable_name = 'y'
1537       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1538                                   dimension_names = (/'station'/), output_type = 'real32' )
1539!
1540!--    E-UTM
1541       variable_name = 'E_UTM'
1542       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1543                                   dimension_names = (/'station'/), output_type = 'real32' )
1544!
1545!--    N-UTM
1546       variable_name = 'N_UTM'
1547       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1548                                   dimension_names = (/'station'/), output_type = 'real32' )
1549!
1550!--    latitude
1551       variable_name = 'lat'
1552       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1553                                   dimension_names = (/'station'/), output_type = 'real32' )
1554!
1555!--    longitude
1556       variable_name = 'lon'
1557       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
1558                                   dimension_names = (/'station'/), output_type = 'real32' )
1559!
1560!--    Set attributes for the coordinate variables. Note, not all coordinates have the same number
1561!--    of attributes.
1562!--    Units
1563       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time',                    &
1564                                   attribute_name = char_unit, value = 'seconds since ' //         &
1565                                   origin_date_time )
1566       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z',                       &
1567                                   attribute_name = char_unit, value = 'm' )
1568       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_h',               &
1569                                   attribute_name = char_unit, value = 'm' )
1570       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'x',                       &
1571                                   attribute_name = char_unit, value = 'm' )
1572       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'y',                       &
1573                                   attribute_name = char_unit, value = 'm' )
1574       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'E_UTM',                   &
1575                                   attribute_name = char_unit, value = 'm' )
1576       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'N_UTM',                   &
1577                                   attribute_name = char_unit, value = 'm' )
1578       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lat',                     &
1579                                   attribute_name = char_unit, value = 'degrees_north' )
1580       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lon',                     &
1581                                   attribute_name = char_unit, value = 'degrees_east' )
1582!
1583!--    Long name
1584       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_name',            &
1585                                   attribute_name = char_long, value = 'station name')
1586       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time',                    &
1587                                   attribute_name = char_long, value = 'time')
1588       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z',                       &
1589                                   attribute_name = char_long, value = 'height above origin' )
1590       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_h',               &
1591                                   attribute_name = char_long, value = 'surface altitude' )
1592       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'x',                       &
1593                                   attribute_name = char_long,                                     &
1594                                   value = 'distance to origin in x-direction')
1595       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'y',                       &
1596                                   attribute_name = char_long,                                     &
1597                                   value = 'distance to origin in y-direction')
1598       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'E_UTM',                   &
1599                                   attribute_name = char_long, value = 'easting' )
1600       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'N_UTM',                   &
1601                                   attribute_name = char_long, value = 'northing' )
1602       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lat',                     &
1603                                   attribute_name = char_long, value = 'latitude' )
1604       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lon',                     &
1605                                   attribute_name = char_long, value = 'longitude' )
1606!
1607!--    Standard name
1608       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_name',            &
1609                                   attribute_name = char_standard, value = 'platform_name')
1610       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time',                    &
1611                                   attribute_name = char_standard, value = 'time')
1612       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z',                       &
1613                                   attribute_name = char_standard,                                 &
1614                                   value = 'height_above_mean_sea_level' )
1615       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_h',               &
1616                                   attribute_name = char_standard, value = 'surface_altitude' )
1617       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'E_UTM',                   &
1618                                   attribute_name = char_standard,                                 &
1619                                   value = 'projection_x_coordinate' )
1620       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'N_UTM',                   &
1621                                   attribute_name = char_standard,                                 &
1622                                   value = 'projection_y_coordinate' )
1623       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lat',                     &
1624                                   attribute_name = char_standard, value = 'latitude' )
1625       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lon',                     &
1626                                   attribute_name = char_standard, value = 'longitude' )
1627!
1628!--    Axis
1629       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time',                    &
1630                                   attribute_name = 'axis', value = 'T')
1631       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z',                       &
1632                                   attribute_name = 'axis', value = 'Z' )
1633       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'x',                       &
1634                                   attribute_name = 'axis', value = 'X' )
1635       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'y',                       &
1636                                   attribute_name = 'axis', value = 'Y' )
1637!
1638!--    Set further individual attributes for the coordinate variables.
1639!--    For station name
1640       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_name',            &
1641                                   attribute_name = 'cf_role', value = 'timeseries_id' )
1642!
1643!--    For time
1644       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time',                    &
1645                                   attribute_name = 'calendar', value = 'proleptic_gregorian' )
1646       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time',                    &
1647                                   attribute_name = 'bounds', value = 'time_bounds' )
1648!
1649!--    For vertical reference system
1650       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'vrs',                     &
1651                                   attribute_name = char_long, value = 'vertical reference system' )
1652       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'vrs',                     &
1653                                   attribute_name = 'system_name', value = 'DHHN2016' )
1654!
1655!--    For z
1656       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z',                       &
1657                                   attribute_name = 'positive', value = 'up' )
1658!
1659!--    For coordinate reference system
1660       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1661                                   attribute_name = 'epsg_code', value = coord_ref_sys%epsg_code )
1662       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1663                                   attribute_name = 'false_easting',                               &
1664                                   value = coord_ref_sys%false_easting )
1665       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1666                                   attribute_name = 'false_northing',                              &
1667                                   value = coord_ref_sys%false_northing )
1668       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1669                                   attribute_name = 'grid_mapping_name',                           &
1670                                   value = coord_ref_sys%grid_mapping_name )
1671       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1672                                   attribute_name = 'inverse_flattening',                          &
1673                                   value = coord_ref_sys%inverse_flattening )
1674       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1675                                   attribute_name = 'latitude_of_projection_origin',&
1676                                   value = coord_ref_sys%latitude_of_projection_origin )
1677       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1678                                   attribute_name = char_long, value = coord_ref_sys%long_name )
1679       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1680                                   attribute_name = 'longitude_of_central_meridian',               &
1681                                   value = coord_ref_sys%longitude_of_central_meridian )
1682       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1683                                   attribute_name = 'longitude_of_prime_meridian',                 &
1684                                   value = coord_ref_sys%longitude_of_prime_meridian )
1685       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1686                                   attribute_name = 'scale_factor_at_central_meridian',            &
1687                                   value = coord_ref_sys%scale_factor_at_central_meridian )
1688       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1689                                   attribute_name = 'semi_major_axis',                             &
1690                                   value = coord_ref_sys%semi_major_axis )
1691       return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'crs',                     &
1692                                   attribute_name = char_unit, value = coord_ref_sys%units )
1693!
1694!--    In case of sampled soil quantities, define further dimensions and coordinates.
1695       IF ( vmea(l)%soil_sampling )  THEN
1696!
1697!--       station for soil
1698          ALLOCATE( ndim(1:vmea(l)%ns_soil_tot) )
1699          DO  n = 1, vmea(l)%ns_soil_tot
1700             ndim(n) = n
1701          ENDDO
1702
1703          return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'station_soil',        &
1704                                      output_type = 'int32',                                       &
1705                                      bounds = (/1_iwp,vmea(l)%ns_soil_tot/), values_int32 = ndim )
1706          DEALLOCATE( ndim )
1707!
1708!--       ntime for soil
1709          ALLOCATE( ndim(1:ntimesteps) )
1710          DO  n = 1, ntimesteps
1711             ndim(n) = n
1712          ENDDO
1713
1714          return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'ntime_soil',          &
1715                                      output_type = 'int32', bounds = (/1_iwp,ntimesteps/),        &
1716                                      values_int32 = ndim )
1717          DEALLOCATE( ndim )
1718!
1719!--       time for soil
1720          variable_name = 'time_soil'
1721          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1722                                      dimension_names = (/'station_soil', 'ntime_soil  '/),        &
1723                                      output_type = 'real32' )
1724!
1725!--       station_name for soil
1726          variable_name = 'station_name_soil'
1727          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1728                                      dimension_names = (/ 'max_name_len', 'station_soil' /),      &
1729                                      output_type = 'char' )
1730!
1731!--       z
1732          variable_name = 'z_soil'
1733          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1734                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1735!
1736!--       station_h for soil
1737          variable_name = 'station_h_soil'
1738          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1739                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1740!
1741!--       x soil
1742          variable_name = 'x_soil'
1743          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1744                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1745!
1746!-        y soil
1747          variable_name = 'y_soil'
1748          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1749                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1750!
1751!--       E-UTM soil
1752          variable_name = 'E_UTM_soil'
1753          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1754                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1755!
1756!--       N-UTM soil
1757          variable_name = 'N_UTM_soil'
1758          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1759                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1760!
1761!--       latitude soil
1762          variable_name = 'lat_soil'
1763          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1764                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1765!
1766!--       longitude soil
1767          variable_name = 'lon_soil'
1768          return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,          &
1769                                      dimension_names = (/'station_soil'/), output_type = 'real32' )
1770!
1771!--       Set attributes for the coordinate variables. Note, not all coordinates have the same
1772!--       number of attributes.
1773!--       Units
1774          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time_soil',            &
1775                                      attribute_name = char_unit, value = 'seconds since ' //      &
1776                                      origin_date_time )
1777          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z_soil',               &
1778                                      attribute_name = char_unit, value = 'm' )
1779          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_h_soil',       &
1780                                      attribute_name = char_unit, value = 'm' )
1781          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'x_soil',               &
1782                                      attribute_name = char_unit, value = 'm' )
1783          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'y_soil',               &
1784                                      attribute_name = char_unit, value = 'm' )
1785          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'E_UTM_soil',           &
1786                                      attribute_name = char_unit, value = 'm' )
1787          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'N_UTM_soil',           &
1788                                      attribute_name = char_unit, value = 'm' )
1789          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lat_soil',             &
1790                                      attribute_name = char_unit, value = 'degrees_north' )
1791          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lon_soil',             &
1792                                      attribute_name = char_unit, value = 'degrees_east' )
1793!
1794!--       Long name
1795          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_name_soil',    &
1796                                      attribute_name = char_long, value = 'station name')
1797          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time_soil',            &
1798                                      attribute_name = char_long, value = 'time')
1799          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z_soil',               &
1800                                      attribute_name = char_long, value = 'height above origin' )
1801          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_h_soil',       &
1802                                      attribute_name = char_long, value = 'surface altitude' )
1803          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'x_soil',               &
1804                                      attribute_name = char_long,                                  &
1805                                      value = 'distance to origin in x-direction' )
1806          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'y_soil',               &
1807                                      attribute_name = char_long,                                  &
1808                                      value = 'distance to origin in y-direction' )
1809          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'E_UTM_soil',           &
1810                                      attribute_name = char_long, value = 'easting' )
1811          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'N_UTM_soil',           &
1812                                      attribute_name = char_long, value = 'northing' )
1813          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lat_soil',             &
1814                                      attribute_name = char_long, value = 'latitude' )
1815          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lon_soil',             &
1816                                      attribute_name = char_long, value = 'longitude' )
1817!
1818!--       Standard name
1819          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_name_soil',    &
1820                                      attribute_name = char_standard, value = 'platform_name')
1821          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time_soil',            &
1822                                      attribute_name = char_standard, value = 'time')
1823          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z_soil',               &
1824                                      attribute_name = char_standard,                              &
1825                                      value = 'height_above_mean_sea_level' )
1826          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_h_soil',       &
1827                                      attribute_name = char_standard, value = 'surface_altitude' )
1828          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'E_UTM_soil',           &
1829                                      attribute_name = char_standard,                              &
1830                                      value = 'projection_x_coordinate' )
1831          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'N_UTM_soil',           &
1832                                      attribute_name = char_standard,                              &
1833                                      value = 'projection_y_coordinate' )
1834          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lat_soil',             &
1835                                      attribute_name = char_standard, value = 'latitude' )
1836          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'lon_soil',             &
1837                                      attribute_name = char_standard, value = 'longitude' )
1838!
1839!--       Axis
1840          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time_soil',            &
1841                                      attribute_name = 'axis', value = 'T')
1842          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z_soil',               &
1843                                      attribute_name = 'axis', value = 'Z' )
1844          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'x_soil',               &
1845                                      attribute_name = 'axis', value = 'X' )
1846          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'y_soil',               &
1847                                      attribute_name = 'axis', value = 'Y' )
1848!
1849!--       Set further individual attributes for the coordinate variables.
1850!--       For station name soil
1851          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'station_name_soil',    &
1852                                      attribute_name = 'cf_role', value = 'timeseries_id' )
1853!
1854!--       For time soil
1855          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time_soil',            &
1856                                      attribute_name = 'calendar', value = 'proleptic_gregorian' )
1857          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'time_soil',            &
1858                                      attribute_name = 'bounds', value = 'time_bounds' )
1859!
1860!--       For z soil
1861          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = 'z_soil',               &
1862                                      attribute_name = 'positive', value = 'up' )
1863       ENDIF
1864!
1865!--    Define variables that shall be sampled.
1866       DO  n = 1, vmea(l)%nmeas
1867          variable_name = TRIM( vmea(l)%var_atts(n)%name )
1868!
1869!--       In order to link the correct dimension names, atmosphere and soil variables need to be
1870!--       distinguished.
1871          IF ( vmea(l)%soil_sampling  .AND.                                                        &
1872               ANY( TRIM( vmea(l)%var_atts(n)%name) == soil_vars ) )  THEN
1873
1874             return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,       &
1875                                         dimension_names = (/'station_soil', 'ntime_soil  '/),     &
1876                                         output_type = 'real32' )
1877          ELSE
1878
1879             return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,       &
1880                                         dimension_names = (/'station', 'ntime  '/),               &
1881                                         output_type = 'real32' )
1882          ENDIF
1883!
1884!--       Set variable attributes. Please note, for some variables not all attributes are defined,
1885!--       e.g. standard_name for the horizontal wind components.
1886          CALL vm_set_attributes( vmea(l)%var_atts(n) )
1887
1888          IF ( vmea(l)%var_atts(n)%long_name /= 'none' )  THEN
1889             return_value = dom_def_att( vmea(l)%nc_filename,  variable_name = variable_name,      &
1890                                         attribute_name = char_long,                               &
1891                                         value = TRIM( vmea(l)%var_atts(n)%long_name ) )
1892          ENDIF
1893          IF ( vmea(l)%var_atts(n)%standard_name /= 'none' )  THEN
1894             return_value = dom_def_att( vmea(l)%nc_filename, variable_name = variable_name,       &
1895                                         attribute_name = char_standard,                           &
1896                                         value = TRIM( vmea(l)%var_atts(n)%standard_name ) )
1897          ENDIF
1898          IF ( vmea(l)%var_atts(n)%units /= 'none' )  THEN
1899             return_value = dom_def_att( vmea(l)%nc_filename, variable_name = variable_name,       &
1900                                         attribute_name = char_unit,                               &
1901                                         value = TRIM( vmea(l)%var_atts(n)%units ) )
1902          ENDIF
1903
1904          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = variable_name,          &
1905                                      attribute_name = 'grid_mapping',                             &
1906                                      value = TRIM( vmea(l)%var_atts(n)%grid_mapping ) )
1907
1908          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = variable_name,          &
1909                                      attribute_name = 'coordinates',                              &
1910                                      value = TRIM( vmea(l)%var_atts(n)%coordinates ) )
1911
1912          return_value = dom_def_att( vmea(l)%nc_filename, variable_name = variable_name,          &
1913                                      attribute_name = char_fill,                                  &
1914                                      value = REAL( vmea(l)%var_atts(n)%fill_value, KIND=4 ) )
1915
1916       ENDDO  ! loop over variables per site
1917
1918    ENDDO  ! loop over sites
1919
1920
1921 END SUBROUTINE vm_init_output
1922
1923!--------------------------------------------------------------------------------------------------!
1924! Description:
1925! ------------
1926!> Parallel NetCDF output via data-output module.
1927!--------------------------------------------------------------------------------------------------!
1928 SUBROUTINE vm_data_output
1929
1930    CHARACTER(LEN=100) ::  variable_name  !< name of output variable
1931    CHARACTER(LEN=maximum_name_length), DIMENSION(:), ALLOCATABLE :: station_name  !< string for station name, consecutively ordered
1932
1933    CHARACTER(LEN=1), DIMENSION(:,:), ALLOCATABLE, TARGET ::  output_values_2d_char_target  !< target for output name arrays
1934    CHARACTER(LEN=1), DIMENSION(:,:), POINTER             ::  output_values_2d_char_pointer !< pointer for output name arrays
1935
1936    INTEGER(iwp)       ::  l             !< loop index for the number of sites
1937    INTEGER(iwp)       ::  n             !< loop index for observation points
1938    INTEGER(iwp)       ::  nn            !< loop index for number of characters in a name
1939    INTEGER            ::  return_value  !< returned status value of called function
1940    INTEGER(iwp)       ::  t_ind         !< time index
1941
1942    REAL(wp), DIMENSION(:), ALLOCATABLE           ::  dum_lat                   !< transformed geographical coordinate (latitude)
1943    REAL(wp), DIMENSION(:), ALLOCATABLE           ::  dum_lon                   !< transformed geographical coordinate (longitude)
1944    REAL(wp), DIMENSION(:), ALLOCATABLE           ::  oro_rel                   !< relative altitude of model surface
1945    REAL(wp), DIMENSION(:), POINTER               ::  output_values_1d_pointer  !< pointer for 1d output array
1946    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET   ::  output_values_1d_target   !< target for 1d output array
1947    REAL(wp), DIMENSION(:,:), POINTER             ::  output_values_2d_pointer  !< pointer for 2d output array
1948    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET ::  output_values_2d_target   !< target for 2d output array
1949
1950    CALL cpu_log( log_point_s(26), 'VM output', 'start' )
1951!
1952!-- At the first call of this routine write the spatial coordinates.
1953    IF ( .NOT. initial_write_coordinates )  THEN
1954!
1955!--    Write spatial coordinates.
1956       DO  l = 1, vmea_general%nvm
1957!
1958!--       Skip if no observations were taken.
1959          IF ( vmea(l)%ns_tot == 0  .AND.  vmea(l)%ns_soil_tot == 0 )  CYCLE
1960
1961          ALLOCATE( output_values_1d_target(vmea(l)%start_coord_a:vmea(l)%end_coord_a) )
1962!
1963!--       Output of Easting coordinate. Before output, recalculate EUTM.
1964          output_values_1d_target = init_model%origin_x                                            &
1965                    + REAL( vmea(l)%i(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dx                     &
1966                    * COS( init_model%rotation_angle * pi / 180.0_wp )                             &
1967                    + REAL( vmea(l)%j(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dy                     &
1968                    * SIN( init_model%rotation_angle * pi / 180.0_wp )
1969
1970          output_values_1d_pointer => output_values_1d_target
1971
1972          return_value = dom_write_var( vmea(l)%nc_filename, 'E_UTM',                              &
1973                                        values_realwp_1d = output_values_1d_pointer,               &
1974                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
1975                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
1976!
1977!--       Output of Northing coordinate. Before output, recalculate NUTM.
1978          output_values_1d_target = init_model%origin_y                                            &
1979                    - REAL( vmea(l)%i(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dx                     &
1980                    * SIN( init_model%rotation_angle * pi / 180.0_wp )                             &
1981                    + REAL( vmea(l)%j(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dy                     &
1982                    * COS( init_model%rotation_angle * pi / 180.0_wp )
1983
1984          output_values_1d_pointer => output_values_1d_target
1985          return_value = dom_write_var( vmea(l)%nc_filename, 'N_UTM',                              &
1986                                        values_realwp_1d = output_values_1d_pointer,               &
1987                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
1988                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
1989!
1990!--       Output of longitude and latitude coordinate. Before output, convert it.
1991          ALLOCATE( dum_lat(1:vmea(l)%ns) )
1992          ALLOCATE( dum_lon(1:vmea(l)%ns) )
1993
1994          DO  n = 1, vmea(l)%ns
1995             CALL convert_utm_to_geographic( crs_list,                                             &
1996                                             init_model%origin_x                                   &
1997                                           + REAL( vmea(l)%i(n) + 0.5_wp, KIND = wp ) * dx         &
1998                                           * COS( init_model%rotation_angle * pi / 180.0_wp )      &
1999                                           + REAL( vmea(l)%j(n) + 0.5_wp, KIND = wp ) * dy         &
2000                                           * SIN( init_model%rotation_angle * pi / 180.0_wp ),     &
2001                                             init_model%origin_y                                   &
2002                                           - REAL( vmea(l)%i(n) + 0.5_wp, KIND = wp ) * dx         &
2003                                           * SIN( init_model%rotation_angle * pi / 180.0_wp )      &
2004                                           + REAL( vmea(l)%j(n) + 0.5_wp, KIND = wp ) * dy         &
2005                                           * COS( init_model%rotation_angle * pi / 180.0_wp ),     &
2006                                             dum_lon(n), dum_lat(n) )
2007          ENDDO
2008
2009          output_values_1d_target = dum_lat
2010          output_values_1d_pointer => output_values_1d_target
2011          return_value = dom_write_var( vmea(l)%nc_filename, 'lat',                                &
2012                                        values_realwp_1d = output_values_1d_pointer,               &
2013                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
2014                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
2015
2016          output_values_1d_target = dum_lon
2017          output_values_1d_pointer => output_values_1d_target
2018          return_value = dom_write_var( vmea(l)%nc_filename, 'lon',                                &
2019                                        values_realwp_1d = output_values_1d_pointer,               &
2020                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
2021                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
2022          DEALLOCATE( dum_lat )
2023          DEALLOCATE( dum_lon )
2024!
2025!--       Output of relative height coordinate.
2026!--       Before this is output, first define the relative orographie height and add this to z.
2027          ALLOCATE( oro_rel(1:vmea(l)%ns) )
2028          DO  n = 1, vmea(l)%ns
2029             oro_rel(n) = zw(topo_top_ind(vmea(l)%j(n),vmea(l)%i(n),3))
2030          ENDDO
2031
2032          output_values_1d_target = vmea(l)%zar(1:vmea(l)%ns) + oro_rel(:)
2033          output_values_1d_pointer => output_values_1d_target
2034          return_value = dom_write_var( vmea(l)%nc_filename, 'z',                                  &
2035                                        values_realwp_1d = output_values_1d_pointer,               &
2036                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
2037                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
2038!
2039!--       Write surface altitude for the station. Note, since z is already a relative observation
2040!--       height, station_h must be zero, in order to obtain the observation level.
2041          output_values_1d_target = oro_rel(:)
2042          output_values_1d_pointer => output_values_1d_target
2043          return_value = dom_write_var( vmea(l)%nc_filename, 'station_h',                          &
2044                                        values_realwp_1d = output_values_1d_pointer,               &
2045                                        bounds_start = (/vmea(l)%start_coord_a/),                  &
2046                                        bounds_end   = (/vmea(l)%end_coord_a  /) )
2047
2048          DEALLOCATE( oro_rel )
2049          DEALLOCATE( output_values_1d_target )
2050!
2051!--       Write station name
2052          ALLOCATE ( station_name(vmea(l)%start_coord_a:vmea(l)%end_coord_a) )
2053          ALLOCATE ( output_values_2d_char_target(vmea(l)%start_coord_a:vmea(l)%end_coord_a, &
2054                                                  1:maximum_name_length) )
2055
2056          DO  n = vmea(l)%start_coord_a, vmea(l)%end_coord_a
2057             station_name(n) = REPEAT( ' ', maximum_name_length )
2058             WRITE( station_name(n), '(A,I10.10)') "station", n
2059             DO  nn = 1, maximum_name_length
2060                output_values_2d_char_target(n,nn) = station_name(n)(nn:nn)
2061             ENDDO
2062          ENDDO
2063
2064          output_values_2d_char_pointer => output_values_2d_char_target
2065
2066          return_value = dom_write_var( vmea(l)%nc_filename, 'station_name',                       &
2067                                        values_char_2d = output_values_2d_char_pointer,            &
2068                                        bounds_start = (/ 1, vmea(l)%start_coord_a /),             &
2069                                        bounds_end   = (/ maximum_name_length,                     &
2070                                        vmea(l)%end_coord_a /) )
2071
2072          DEALLOCATE( station_name )
2073          DEALLOCATE( output_values_2d_char_target )
2074!
2075!--       In case of sampled soil quantities, output also the respective coordinate arrays.
2076          IF ( vmea(l)%soil_sampling )  THEN
2077             ALLOCATE( output_values_1d_target(vmea(l)%start_coord_s:vmea(l)%end_coord_s) )
2078!
2079!--          Output of Easting coordinate. Before output, recalculate EUTM.
2080             output_values_1d_target = init_model%origin_x                                         &
2081               + REAL( vmea(l)%i(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dx                     &
2082               * COS( init_model%rotation_angle * pi / 180.0_wp )                                  &
2083               + REAL( vmea(l)%j(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dy                     &
2084               * SIN( init_model%rotation_angle * pi / 180.0_wp )
2085             output_values_1d_pointer => output_values_1d_target
2086             return_value = dom_write_var( vmea(l)%nc_filename, 'E_UTM_soil',                      &
2087                                           values_realwp_1d = output_values_1d_pointer,            &
2088                                           bounds_start = (/vmea(l)%start_coord_s/),               &
2089                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
2090!
2091!--          Output of Northing coordinate. Before output, recalculate NUTM.
2092             output_values_1d_target = init_model%origin_y                                         &
2093               - REAL( vmea(l)%i_soil(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dx                &
2094               * SIN( init_model%rotation_angle * pi / 180.0_wp )                                  &
2095               + REAL( vmea(l)%j_soil(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dy                &
2096               * COS( init_model%rotation_angle * pi / 180.0_wp )
2097
2098             output_values_1d_pointer => output_values_1d_target
2099             return_value = dom_write_var( vmea(l)%nc_filename, 'N_UTM_soil',                      &
2100                                           values_realwp_1d = output_values_1d_pointer,            &
2101                                           bounds_start = (/vmea(l)%start_coord_s/),               &
2102                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
2103!
2104!--          Output of longitude and latitude coordinate. Before output, convert it.
2105             ALLOCATE( dum_lat(1:vmea(l)%ns_soil) )
2106             ALLOCATE( dum_lon(1:vmea(l)%ns_soil) )
2107
2108             DO  n = 1, vmea(l)%ns_soil
2109                CALL convert_utm_to_geographic( crs_list,                                          &
2110                                                init_model%origin_x                                &
2111                                              + REAL( vmea(l)%i_soil(n) + 0.5_wp, KIND = wp ) * dx &
2112                                              * COS( init_model%rotation_angle * pi / 180.0_wp )   &
2113                                              + REAL( vmea(l)%j_soil(n) + 0.5_wp, KIND = wp ) * dy &
2114                                              * SIN( init_model%rotation_angle * pi / 180.0_wp ),  &
2115                                                init_model%origin_y                                &
2116                                              - REAL( vmea(l)%i_soil(n) + 0.5_wp, KIND = wp ) * dx &
2117                                              * SIN( init_model%rotation_angle * pi / 180.0_wp )   &
2118                                              + REAL( vmea(l)%j_soil(n) + 0.5_wp, KIND = wp ) * dy &
2119                                              * COS( init_model%rotation_angle * pi / 180.0_wp ),  &
2120                                                dum_lon(n), dum_lat(n) )
2121             ENDDO
2122
2123             output_values_1d_target = dum_lat
2124             output_values_1d_pointer => output_values_1d_target
2125             return_value = dom_write_var( vmea(l)%nc_filename, 'lat_soil',                        &
2126                                           values_realwp_1d = output_values_1d_pointer,            &
2127                                           bounds_start = (/vmea(l)%start_coord_s/),               &
2128                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
2129
2130             output_values_1d_target = dum_lon
2131             output_values_1d_pointer => output_values_1d_target
2132             return_value = dom_write_var( vmea(l)%nc_filename, 'lon_soil',                        &
2133                                           values_realwp_1d = output_values_1d_pointer,            &
2134                                           bounds_start = (/vmea(l)%start_coord_s/),               &
2135                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
2136             DEALLOCATE( dum_lat )
2137             DEALLOCATE( dum_lon )
2138!
2139!--          Output of relative height coordinate.
2140!--          Before this is output, first define the relative orographie height and add this to z.
2141             ALLOCATE( oro_rel(1:vmea(l)%ns_soil) )
2142             DO  n = 1, vmea(l)%ns_soil
2143                oro_rel(n) = zw(topo_top_ind(vmea(l)%j_soil(n),vmea(l)%i_soil(n),3))
2144             ENDDO
2145
2146             output_values_1d_target = vmea(l)%depth(1:vmea(l)%ns_soil) + oro_rel(:)
2147             output_values_1d_pointer => output_values_1d_target
2148             return_value = dom_write_var( vmea(l)%nc_filename, 'z_soil',                          &
2149                                           values_realwp_1d = output_values_1d_pointer,            &
2150                                           bounds_start = (/vmea(l)%start_coord_s/),               &
2151                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
2152!
2153!--          Write surface altitude for the station. Note, since z is already a relative observation
2154!--          height, station_h must be zero, in order to obtain the observation level.
2155             output_values_1d_target = oro_rel(:)
2156             output_values_1d_pointer => output_values_1d_target
2157             return_value = dom_write_var( vmea(l)%nc_filename, 'station_h_soil',                  &
2158                                           values_realwp_1d = output_values_1d_pointer,            &
2159                                           bounds_start = (/vmea(l)%start_coord_s/),               &
2160                                           bounds_end   = (/vmea(l)%end_coord_s  /) )
2161
2162             DEALLOCATE( oro_rel )
2163             DEALLOCATE( output_values_1d_target )
2164!
2165!--          Write station name
2166             ALLOCATE ( station_name(vmea(l)%start_coord_s:vmea(l)%end_coord_s) )
2167             ALLOCATE ( output_values_2d_char_target(vmea(l)%start_coord_s:vmea(l)%end_coord_s,    &
2168                                                     1:maximum_name_length) )
2169
2170             DO  n = vmea(l)%start_coord_s, vmea(l)%end_coord_s
2171                station_name(n) = REPEAT( ' ', maximum_name_length )
2172                WRITE( station_name(n), '(A,I10.10)') "station", n
2173                DO  nn = 1, maximum_name_length
2174                   output_values_2d_char_target(n,nn) = station_name(n)(nn:nn)
2175                ENDDO
2176             ENDDO
2177             output_values_2d_char_pointer => output_values_2d_char_target
2178
2179             return_value = dom_write_var( vmea(l)%nc_filename, 'station_name_soil',               &
2180                                           values_char_2d = output_values_2d_char_pointer,         &
2181                                           bounds_start = (/ 1, vmea(l)%start_coord_s /),          &
2182                                           bounds_end   = (/ maximum_name_length,                  &
2183                                           vmea(l)%end_coord_s   /) )
2184
2185             DEALLOCATE( station_name )
2186             DEALLOCATE( output_values_2d_char_target )
2187
2188          ENDIF
2189
2190       ENDDO  ! loop over sites
2191
2192       initial_write_coordinates = .TRUE.
2193    ENDIF
2194!
2195!-- Loop over all sites.
2196    DO  l = 1, vmea_general%nvm
2197!
2198!--    Skip if no observations were taken.
2199       IF ( vmea(l)%ns_tot == 0  .AND.  vmea(l)%ns_soil_tot == 0 )  CYCLE
2200!
2201!--    Determine time index in file.
2202       t_ind = vmea(l)%file_time_index + 1
2203!
2204!--    Write output variables. Distinguish between atmosphere and soil variables.
2205       DO  n = 1, vmea(l)%nmeas
2206          IF ( vmea(l)%soil_sampling  .AND.                                                        &
2207            ANY( TRIM( vmea(l)%var_atts(n)%name) == soil_vars ) )  THEN
2208!
2209!--          Write time coordinate to file
2210             variable_name = 'time_soil'
2211             ALLOCATE( output_values_2d_target(t_ind:t_ind,vmea(l)%start_coord_s:vmea(l)%end_coord_s) )
2212             output_values_2d_target(t_ind,:) = time_since_reference_point
2213             output_values_2d_pointer => output_values_2d_target
2214
2215             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
2216                                           values_realwp_2d = output_values_2d_pointer,            &
2217                                           bounds_start = (/vmea(l)%start_coord_s, t_ind/),        &
2218                                           bounds_end   = (/vmea(l)%end_coord_s, t_ind /) )
2219
2220             variable_name = TRIM( vmea(l)%var_atts(n)%name )
2221             output_values_2d_target(t_ind,:) = vmea(l)%measured_vars_soil(:,n)
2222             output_values_2d_pointer => output_values_2d_target
2223             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
2224                                           values_realwp_2d = output_values_2d_pointer,            &
2225                                           bounds_start = (/vmea(l)%start_coord_s, t_ind/),        &
2226                                           bounds_end   = (/vmea(l)%end_coord_s, t_ind  /) )
2227             DEALLOCATE( output_values_2d_target )
2228          ELSE
2229!
2230!--          Write time coordinate to file
2231             variable_name = 'time'
2232             ALLOCATE( output_values_2d_target(t_ind:t_ind,vmea(l)%start_coord_a:vmea(l)%end_coord_a) )
2233             output_values_2d_target(t_ind,:) = time_since_reference_point
2234             output_values_2d_pointer => output_values_2d_target
2235
2236             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
2237                                           values_realwp_2d = output_values_2d_pointer,            &
2238                                           bounds_start = (/vmea(l)%start_coord_a, t_ind/),        &
2239                                           bounds_end   = (/vmea(l)%end_coord_a, t_ind/) )
2240
2241             variable_name = TRIM( vmea(l)%var_atts(n)%name )
2242
2243             output_values_2d_target(t_ind,:) = vmea(l)%measured_vars(:,n)
2244             output_values_2d_pointer => output_values_2d_target
2245             return_value = dom_write_var( vmea(l)%nc_filename, variable_name,                     &
2246                                           values_realwp_2d = output_values_2d_pointer,            &
2247                                           bounds_start = (/ vmea(l)%start_coord_a, t_ind /),      &
2248                                           bounds_end   = (/ vmea(l)%end_coord_a, t_ind /) )
2249
2250             DEALLOCATE( output_values_2d_target )
2251          ENDIF
2252       ENDDO
2253!
2254!--    Update number of written time indices
2255       vmea(l)%file_time_index = t_ind
2256
2257    ENDDO  ! loop over sites
2258
2259    CALL cpu_log( log_point_s(26), 'VM output', 'stop' )
2260
2261
2262 END SUBROUTINE vm_data_output
2263
2264!--------------------------------------------------------------------------------------------------!
2265! Description:
2266! ------------
2267!> Sampling of the actual quantities along the observation coordinates
2268!--------------------------------------------------------------------------------------------------!
2269 SUBROUTINE vm_sampling
2270
2271    USE radiation_model_mod,                                                                       &
2272        ONLY:  radiation
2273
2274    USE surface_mod,                                                                               &
2275        ONLY:  surf_def_h,                                                                         &
2276               surf_lsm_h,                                                                         &
2277               surf_usm_h
2278
2279     INTEGER(iwp) ::  i         !< grid index in x-direction
2280     INTEGER(iwp) ::  j         !< grid index in y-direction
2281     INTEGER(iwp) ::  k         !< grid index in z-direction
2282     INTEGER(iwp) ::  ind_chem  !< dummy index to identify chemistry variable and translate it from (UC)2 standard to interal naming
2283     INTEGER(iwp) ::  l         !< running index over the number of stations
2284     INTEGER(iwp) ::  m         !< running index over all virtual observation coordinates
2285     INTEGER(iwp) ::  mm        !< index of surface element which corresponds to the virtual observation coordinate
2286     INTEGER(iwp) ::  n         !< running index over all measured variables at a station
2287     INTEGER(iwp) ::  nn        !< running index over the number of chemcal species
2288
2289     LOGICAL ::  match_lsm  !< flag indicating natural-type surface
2290     LOGICAL ::  match_usm  !< flag indicating urban-type surface
2291
2292     REAL(wp) ::  e_s   !< saturation water vapor pressure
2293     REAL(wp) ::  q_s   !< saturation mixing ratio
2294     REAL(wp) ::  q_wv  !< mixing ratio
2295
2296     CALL cpu_log( log_point_s(27), 'VM sampling', 'start' )
2297!
2298!--  Loop over all sites.
2299     DO  l = 1, vmea_general%nvm
2300!
2301!--     At the beginning, set _FillValues
2302        IF ( ALLOCATED( vmea(l)%measured_vars ) ) vmea(l)%measured_vars = vmea(l)%fillout
2303        IF ( ALLOCATED( vmea(l)%measured_vars_soil ) ) vmea(l)%measured_vars_soil = vmea(l)%fillout
2304!
2305!--     Loop over all variables measured at this site.
2306        DO  n = 1, vmea(l)%nmeas
2307
2308           SELECT CASE ( TRIM( vmea(l)%var_atts(n)%name ) )
2309
2310              CASE ( 'theta' ) ! potential temperature
2311                 IF ( .NOT. neutral )  THEN
2312                    DO  m = 1, vmea(l)%ns
2313                       k = vmea(l)%k(m)
2314                       j = vmea(l)%j(m)
2315                       i = vmea(l)%i(m)
2316                       vmea(l)%measured_vars(m,n) = pt(k,j,i)
2317                    ENDDO
2318                 ENDIF
2319
2320              CASE ( 'ta' ) ! absolute temperature
2321                 IF ( .NOT. neutral )  THEN
2322                    DO  m = 1, vmea(l)%ns
2323                       k = vmea(l)%k(m)
2324                       j = vmea(l)%j(m)
2325                       i = vmea(l)%i(m)
2326                       vmea(l)%measured_vars(m,n) = pt(k,j,i) * exner( k ) - degc_to_k
2327                    ENDDO
2328                 ENDIF
2329
2330              CASE ( 't_va' )
2331
2332              CASE ( 'hus' ) ! mixing ratio
2333                 IF ( humidity )  THEN
2334                    DO  m = 1, vmea(l)%ns
2335                       k = vmea(l)%k(m)
2336                       j = vmea(l)%j(m)
2337                       i = vmea(l)%i(m)
2338                       vmea(l)%measured_vars(m,n) = q(k,j,i)
2339                    ENDDO
2340                 ENDIF
2341
2342              CASE ( 'haa' ) ! absolute humidity
2343                 IF ( humidity )  THEN
2344                    DO  m = 1, vmea(l)%ns
2345                       k = vmea(l)%k(m)
2346                       j = vmea(l)%j(m)
2347                       i = vmea(l)%i(m)
2348                       vmea(l)%measured_vars(m,n) = ( q(k,j,i) / ( 1.0_wp - q(k,j,i) ) ) * rho_air(k)
2349                    ENDDO
2350                 ENDIF
2351
2352              CASE ( 'pwv' ) ! water vapor partial pressure
2353                 IF ( humidity )  THEN
2354!                     DO  m = 1, vmea(l)%ns
2355!                        k = vmea(l)%k(m)
2356!                        j = vmea(l)%j(m)
2357!                        i = vmea(l)%i(m)
2358!                        vmea(l)%measured_vars(m,n) = ( q(k,j,i) / ( 1.0_wp - q(k,j,i) ) )          &
2359!                                                     * rho_air(k)
2360!                     ENDDO
2361                 ENDIF
2362
2363              CASE ( 'hur' ) ! relative humidity
2364                 IF ( humidity )  THEN
2365                    DO  m = 1, vmea(l)%ns
2366                       k = vmea(l)%k(m)
2367                       j = vmea(l)%j(m)
2368                       i = vmea(l)%i(m)
2369!
2370!--                    Calculate actual temperature, water vapor saturation pressure and, based on
2371!--                    this, the saturation mixing ratio.
2372                       e_s  = magnus( exner(k) * pt(k,j,i) )
2373                       q_s  = rd_d_rv * e_s / ( hyp(k) - e_s )
2374                       q_wv = ( q(k,j,i) / ( 1.0_wp - q(k,j,i) ) ) * rho_air(k)
2375
2376                       vmea(l)%measured_vars(m,n) = q_wv / ( q_s + 1E-10_wp )
2377                    ENDDO
2378                 ENDIF
2379
2380              CASE ( 'u', 'ua' ) ! u-component
2381                 DO  m = 1, vmea(l)%ns
2382                    k = vmea(l)%k(m)
2383                    j = vmea(l)%j(m)
2384                    i = vmea(l)%i(m)
2385                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( u(k,j,i) + u(k,j,i+1) )
2386                 ENDDO
2387
2388              CASE ( 'v', 'va' ) ! v-component
2389                 DO  m = 1, vmea(l)%ns
2390                    k = vmea(l)%k(m)
2391                    j = vmea(l)%j(m)
2392                    i = vmea(l)%i(m)
2393                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( v(k,j,i) + v(k,j+1,i) )
2394                 ENDDO
2395
2396              CASE ( 'w' ) ! w-component
2397                 DO  m = 1, vmea(l)%ns
2398                    k = MAX ( 1, vmea(l)%k(m) )
2399                    j = vmea(l)%j(m)
2400                    i = vmea(l)%i(m)
2401                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( w(k,j,i) + w(k-1,j,i) )
2402                 ENDDO
2403
2404              CASE ( 'wspeed' ) ! horizontal wind speed
2405                 DO  m = 1, vmea(l)%ns
2406                    k = vmea(l)%k(m)
2407                    j = vmea(l)%j(m)
2408                    i = vmea(l)%i(m)
2409                    vmea(l)%measured_vars(m,n) = SQRT(   ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) )**2 &
2410                                                       + ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) )**2 &
2411                                                     )
2412                 ENDDO
2413
2414              CASE ( 'wdir' ) ! wind direction
2415                 DO  m = 1, vmea(l)%ns
2416                    k = vmea(l)%k(m)
2417                    j = vmea(l)%j(m)
2418                    i = vmea(l)%i(m)
2419
2420                    vmea(l)%measured_vars(m,n) = 180.0_wp + 180.0_wp / pi * ATAN2(                 &
2421                                                               0.5_wp * ( v(k,j,i) + v(k,j+1,i) ), &
2422                                                               0.5_wp * ( u(k,j,i) + u(k,j,i+1) )  &
2423                                                                                 )
2424                 ENDDO
2425
2426              CASE ( 'utheta' )
2427                 DO  m = 1, vmea(l)%ns
2428                    k = vmea(l)%k(m)
2429                    j = vmea(l)%j(m)
2430                    i = vmea(l)%i(m)
2431                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) * pt(k,j,i)
2432                 ENDDO
2433
2434              CASE ( 'vtheta' )
2435                 DO  m = 1, vmea(l)%ns
2436                    k = vmea(l)%k(m)
2437                    j = vmea(l)%j(m)
2438                    i = vmea(l)%i(m)
2439                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) * pt(k,j,i)
2440                 ENDDO
2441
2442              CASE ( 'wtheta' )
2443                 DO  m = 1, vmea(l)%ns
2444                    k = MAX ( 1, vmea(l)%k(m) )
2445                    j = vmea(l)%j(m)
2446                    i = vmea(l)%i(m)
2447                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( w(k-1,j,i) + w(k,j,i) ) * pt(k,j,i)
2448                 ENDDO
2449
2450              CASE ( 'uqv' )
2451                 IF ( humidity )  THEN
2452                    DO  m = 1, vmea(l)%ns
2453                       k = vmea(l)%k(m)
2454                       j = vmea(l)%j(m)
2455                       i = vmea(l)%i(m)
2456                       vmea(l)%measured_vars(m,n) = 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) * q(k,j,i)
2457                    ENDDO
2458                 ENDIF
2459
2460              CASE ( 'vqv' )
2461                 IF ( humidity )  THEN
2462                    DO  m = 1, vmea(l)%ns
2463                       k = vmea(l)%k(m)
2464                       j = vmea(l)%j(m)
2465                       i = vmea(l)%i(m)
2466                       vmea(l)%measured_vars(m,n) = 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) * q(k,j,i)
2467                    ENDDO
2468                 ENDIF
2469
2470              CASE ( 'wqv' )
2471                 IF ( humidity )  THEN
2472                    DO  m = 1, vmea(l)%ns
2473                       k = MAX ( 1, vmea(l)%k(m) )
2474                       j = vmea(l)%j(m)
2475                       i = vmea(l)%i(m)
2476                       vmea(l)%measured_vars(m,n) = 0.5_wp * ( w(k-1,j,i) + w(k,j,i) ) * q(k,j,i)
2477                    ENDDO
2478                 ENDIF
2479
2480              CASE ( 'uw' )
2481                 DO  m = 1, vmea(l)%ns
2482                    k = MAX ( 1, vmea(l)%k(m) )
2483                    j = vmea(l)%j(m)
2484                    i = vmea(l)%i(m)
2485                    vmea(l)%measured_vars(m,n) = 0.25_wp * ( w(k-1,j,i) + w(k,j,i) ) *             &
2486                                                           ( u(k,j,i)   + u(k,j,i+1) )
2487                 ENDDO
2488
2489              CASE ( 'vw' )
2490                 DO  m = 1, vmea(l)%ns
2491                    k = MAX ( 1, vmea(l)%k(m) )
2492                    j = vmea(l)%j(m)
2493                    i = vmea(l)%i(m)
2494                    vmea(l)%measured_vars(m,n) = 0.25_wp * ( w(k-1,j,i) + w(k,j,i) ) *             &
2495                                                           ( v(k,j,i)   + v(k,j+1,i) )
2496                 ENDDO
2497
2498              CASE ( 'uv' )
2499                 DO  m = 1, vmea(l)%ns
2500                    k = vmea(l)%k(m)
2501                    j = vmea(l)%j(m)
2502                    i = vmea(l)%i(m)
2503                    vmea(l)%measured_vars(m,n) = 0.25_wp * ( u(k,j,i)   + u(k,j,i+1) ) *           &
2504                                                           ( v(k,j,i)   + v(k,j+1,i) )
2505                 ENDDO
2506!
2507!--           Chemistry variables. List of variables that may need extension. Note, gas species in
2508!--           PALM are in ppm and no distinction is made between mole-fraction and concentration
2509!--           quantities (all are output in ppm so far).
2510              CASE ( 'mcpm1', 'mcpm2p5', 'mcpm10', 'mfno', 'mfno2', 'mcno', 'mcno2', 'tro3' )
2511                 IF ( air_chemistry )  THEN
2512!
2513!--                 First, search for the measured variable in the chem_vars
2514!--                 list, in order to get the internal name of the variable.
2515                    DO  nn = 1, UBOUND( chem_vars, 2 )
2516                       IF ( TRIM( vmea(l)%var_atts(n)%name ) ==                                    &
2517                            TRIM( chem_vars(0,nn) ) )  ind_chem = nn
2518                    ENDDO
2519!
2520!--                 Run loop over all chemical species, if the measured variable matches the interal
2521!--                 name, sample the variable. Note, nvar as a chemistry-module variable.
2522                    DO  nn = 1, nvar
2523                       IF ( TRIM( chem_vars(1,ind_chem) ) == TRIM( chem_species(nn)%name ) )  THEN
2524                          DO  m = 1, vmea(l)%ns
2525                             k = vmea(l)%k(m)
2526                             j = vmea(l)%j(m)
2527                             i = vmea(l)%i(m)
2528                             vmea(l)%measured_vars(m,n) = chem_species(nn)%conc(k,j,i)
2529                          ENDDO
2530                       ENDIF
2531                    ENDDO
2532                 ENDIF
2533
2534              CASE ( 'us' ) ! friction velocity
2535                 DO  m = 1, vmea(l)%ns
2536!
2537!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
2538!--                 limit the indices.
2539                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2540                    j = MERGE( j           , nyn, j            < nyn )
2541                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2542                    i = MERGE( i           , nxr, i            < nxr )
2543
2544                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
2545                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%us(mm)
2546                    ENDDO
2547                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2548                       vmea(l)%measured_vars(m,n) = surf_lsm_h%us(mm)
2549                    ENDDO
2550                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2551                       vmea(l)%measured_vars(m,n) = surf_usm_h%us(mm)
2552                    ENDDO
2553                 ENDDO
2554
2555              CASE ( 'thetas' ) ! scaling parameter temperature
2556                 DO  m = 1, vmea(l)%ns
2557!
2558!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
2559!-                  limit the indices.
2560                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2561                    j = MERGE( j           , nyn, j            < nyn )
2562                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2563                    i = MERGE( i           , nxr, i            < nxr )
2564
2565                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
2566                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%ts(mm)
2567                    ENDDO
2568                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2569                       vmea(l)%measured_vars(m,n) = surf_lsm_h%ts(mm)
2570                    ENDDO
2571                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2572                       vmea(l)%measured_vars(m,n) = surf_usm_h%ts(mm)
2573                    ENDDO
2574                 ENDDO
2575
2576              CASE ( 'hfls' ) ! surface latent heat flux
2577                 DO  m = 1, vmea(l)%ns
2578!
2579!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
2580!--                 limit the indices.
2581                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2582                    j = MERGE( j           , nyn, j            < nyn )
2583                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2584                    i = MERGE( i           , nxr, i            < nxr )
2585
2586                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
2587                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%qsws(mm)
2588                    ENDDO
2589                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2590                       vmea(l)%measured_vars(m,n) = surf_lsm_h%qsws(mm)
2591                    ENDDO
2592                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2593                       vmea(l)%measured_vars(m,n) = surf_usm_h%qsws(mm)
2594                    ENDDO
2595                 ENDDO
2596
2597              CASE ( 'hfss' ) ! surface sensible heat flux
2598                 DO  m = 1, vmea(l)%ns
2599!
2600!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
2601!--                 limit the indices.
2602                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2603                    j = MERGE( j           , nyn, j            < nyn )
2604                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2605                    i = MERGE( i           , nxr, i            < nxr )
2606
2607                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
2608                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%shf(mm)
2609                    ENDDO
2610                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2611                       vmea(l)%measured_vars(m,n) = surf_lsm_h%shf(mm)
2612                    ENDDO
2613                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2614                       vmea(l)%measured_vars(m,n) = surf_usm_h%shf(mm)
2615                    ENDDO
2616                 ENDDO
2617
2618              CASE ( 'hfdg' ) ! ground heat flux
2619                 DO  m = 1, vmea(l)%ns
2620!
2621!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
2622!--                 limit the indices.
2623                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2624                    j = MERGE( j           , nyn, j            < nyn )
2625                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2626                    i = MERGE( i           , nxr, i            < nxr )
2627
2628                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2629                       vmea(l)%measured_vars(m,n) = surf_lsm_h%ghf(mm)
2630                    ENDDO
2631                 ENDDO
2632
2633              CASE ( 'lwcs' )  ! liquid water of soil layer
2634!                  DO  m = 1, vmea(l)%ns
2635! !
2636! !--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
2637! !--                 limit the indices.
2638!                     j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2639!                     j = MERGE( j           , nyn, j            < nyn )
2640!                     i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2641!                     i = MERGE( i           , nxr, i            < nxr )
2642!
2643!                     DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2644!                        vmea(l)%measured_vars(m,n) = ?
2645!                     ENDDO
2646!                  ENDDO
2647
2648              CASE ( 'rnds' ) ! surface net radiation
2649                 IF ( radiation )  THEN
2650                    DO  m = 1, vmea(l)%ns
2651!
2652!--                    Surface data is only available on inner subdomains, not on ghost points.
2653!--                    Hence, limit the indices.
2654                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2655                       j = MERGE( j           , nyn, j            < nyn )
2656                       i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2657                       i = MERGE( i           , nxr, i            < nxr )
2658
2659                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2660                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_net(mm)
2661                       ENDDO
2662                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2663                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_net(mm)
2664                       ENDDO
2665                    ENDDO
2666                 ENDIF
2667
2668              CASE ( 'rsus' ) ! surface shortwave out
2669                 IF ( radiation )  THEN
2670                    DO  m = 1, vmea(l)%ns
2671!
2672!--                    Surface data is only available on inner subdomains, not on ghost points.
2673!--                    Hence, limit the indices.
2674                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2675                       j = MERGE( j           , nyn, j            < nyn )
2676                       i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2677                       i = MERGE( i           , nxr, i            < nxr )
2678
2679                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2680                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_sw_out(mm)
2681                       ENDDO
2682                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2683                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_sw_out(mm)
2684                       ENDDO
2685                    ENDDO
2686                 ENDIF
2687
2688              CASE ( 'rsds' ) ! surface shortwave in
2689                 IF ( radiation )  THEN
2690                    DO  m = 1, vmea(l)%ns
2691!
2692!--                    Surface data is only available on inner subdomains, not on ghost points.
2693!--                    Hence, limit the indices.
2694                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2695                       j = MERGE( j           , nyn, j            < nyn )
2696                       i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2697                       i = MERGE( i           , nxr, i            < nxr )
2698
2699                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2700                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_sw_in(mm)
2701                       ENDDO
2702                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2703                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_sw_in(mm)
2704                       ENDDO
2705                    ENDDO
2706                 ENDIF
2707
2708              CASE ( 'rlus' ) ! surface longwave out
2709                 IF ( radiation )  THEN
2710                    DO  m = 1, vmea(l)%ns
2711!
2712!--                    Surface data is only available on inner subdomains, not on ghost points.
2713!--                    Hence, limit the indices.
2714                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2715                       j = MERGE( j           , nyn, j            < nyn )
2716                       i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2717                       i = MERGE( i           , nxr, i            < nxr )
2718
2719                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2720                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_lw_out(mm)
2721                       ENDDO
2722                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2723                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_lw_out(mm)
2724                       ENDDO
2725                    ENDDO
2726                 ENDIF
2727
2728              CASE ( 'rlds' ) ! surface longwave in
2729                 IF ( radiation )  THEN
2730                    DO  m = 1, vmea(l)%ns
2731!
2732!--                    Surface data is only available on inner subdomains, not on ghost points.
2733!--                    Hence, limit the indices.
2734                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2735                       j = MERGE( j           , nyn, j            < nyn )
2736                       i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2737                       i = MERGE( i           , nxr, i            < nxr )
2738
2739                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2740                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_lw_in(mm)
2741                       ENDDO
2742                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2743                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_lw_in(mm)
2744                       ENDDO
2745                    ENDDO
2746                 ENDIF
2747
2748              CASE ( 'rsd' ) ! shortwave in
2749                 IF ( radiation )  THEN
2750                    IF ( radiation_scheme /= 'rrtmg' )  THEN
2751                       DO  m = 1, vmea(l)%ns
2752                          k = 0
2753                          j = vmea(l)%j(m)
2754                          i = vmea(l)%i(m)
2755                          vmea(l)%measured_vars(m,n) = rad_sw_in(k,j,i)
2756                       ENDDO
2757                    ELSE
2758                       DO  m = 1, vmea(l)%ns
2759                          k = vmea(l)%k(m)
2760                          j = vmea(l)%j(m)
2761                          i = vmea(l)%i(m)
2762                          vmea(l)%measured_vars(m,n) = rad_sw_in(k,j,i)
2763                       ENDDO
2764                    ENDIF
2765                 ENDIF
2766
2767              CASE ( 'rsu' ) ! shortwave out
2768                 IF ( radiation )  THEN
2769                    IF ( radiation_scheme /= 'rrtmg' )  THEN
2770                       DO  m = 1, vmea(l)%ns
2771                          k = 0
2772                          j = vmea(l)%j(m)
2773                          i = vmea(l)%i(m)
2774                          vmea(l)%measured_vars(m,n) = rad_sw_out(k,j,i)
2775                       ENDDO
2776                    ELSE
2777                       DO  m = 1, vmea(l)%ns
2778                          k = vmea(l)%k(m)
2779                          j = vmea(l)%j(m)
2780                          i = vmea(l)%i(m)
2781                          vmea(l)%measured_vars(m,n) = rad_sw_out(k,j,i)
2782                       ENDDO
2783                    ENDIF
2784                 ENDIF
2785
2786              CASE ( 'rlu' ) ! longwave out
2787                 IF ( radiation )  THEN
2788                    IF ( radiation_scheme /= 'rrtmg' )  THEN
2789                       DO  m = 1, vmea(l)%ns
2790                          k = 0
2791                          j = vmea(l)%j(m)
2792                          i = vmea(l)%i(m)
2793                          vmea(l)%measured_vars(m,n) = rad_lw_out(k,j,i)
2794                       ENDDO
2795                    ELSE
2796                       DO  m = 1, vmea(l)%ns
2797                          k = vmea(l)%k(m)
2798                          j = vmea(l)%j(m)
2799                          i = vmea(l)%i(m)
2800                          vmea(l)%measured_vars(m,n) = rad_lw_out(k,j,i)
2801                       ENDDO
2802                    ENDIF
2803                 ENDIF
2804
2805              CASE ( 'rld' ) ! longwave in
2806                 IF ( radiation )  THEN
2807                    IF ( radiation_scheme /= 'rrtmg' )  THEN
2808                       DO  m = 1, vmea(l)%ns
2809                          k = 0
2810!
2811!--                       Surface data is only available on inner subdomains, not on ghost points.
2812!--                       Hence, limit the indices.
2813                          j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2814                          j = MERGE( j           , nyn, j            < nyn )
2815                          i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2816                          i = MERGE( i           , nxr, i            < nxr )
2817
2818                          vmea(l)%measured_vars(m,n) = rad_lw_in(k,j,i)
2819                       ENDDO
2820                    ELSE
2821                       DO  m = 1, vmea(l)%ns
2822                          k = vmea(l)%k(m)
2823                          j = vmea(l)%j(m)
2824                          i = vmea(l)%i(m)
2825                          vmea(l)%measured_vars(m,n) = rad_lw_in(k,j,i)
2826                       ENDDO
2827                    ENDIF
2828                 ENDIF
2829
2830              CASE ( 'rsddif' ) ! shortwave in, diffuse part
2831                 IF ( radiation )  THEN
2832                    DO  m = 1, vmea(l)%ns
2833                       j = vmea(l)%j(m)
2834                       i = vmea(l)%i(m)
2835
2836                       vmea(l)%measured_vars(m,n) = rad_sw_in_diff(j,i)
2837                    ENDDO
2838                 ENDIF
2839
2840              CASE ( 't_soil' ) ! soil and wall temperature
2841                 DO  m = 1, vmea(l)%ns_soil
2842                    j = MERGE( vmea(l)%j_soil(m), nys, vmea(l)%j_soil(m) > nys )
2843                    j = MERGE( j                , nyn, j                 < nyn )
2844                    i = MERGE( vmea(l)%i_soil(m), nxl, vmea(l)%i_soil(m) > nxl )
2845                    i = MERGE( i                , nxr, i                 < nxr )
2846                    k = vmea(l)%k_soil(m)
2847
2848                    match_lsm = surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i)
2849                    match_usm = surf_usm_h%start_index(j,i) <= surf_usm_h%end_index(j,i)
2850
2851                    IF ( match_lsm )  THEN
2852                       mm = surf_lsm_h%start_index(j,i)
2853                       vmea(l)%measured_vars_soil(m,n) = t_soil_h%var_2d(k,mm)
2854                    ENDIF
2855
2856                    IF ( match_usm )  THEN
2857                       mm = surf_usm_h%start_index(j,i)
2858                       vmea(l)%measured_vars_soil(m,n) = t_wall_h(k,mm)
2859                    ENDIF
2860                 ENDDO
2861
2862              CASE ( 'm_soil' ) ! soil moisture
2863                 DO  m = 1, vmea(l)%ns_soil
2864                    j = MERGE( vmea(l)%j_soil(m), nys, vmea(l)%j_soil(m) > nys )
2865                    j = MERGE( j                , nyn, j                 < nyn )
2866                    i = MERGE( vmea(l)%i_soil(m), nxl, vmea(l)%i_soil(m) > nxl )
2867                    i = MERGE( i                , nxr, i                 < nxr )
2868                    k = vmea(l)%k_soil(m)
2869
2870                    match_lsm = surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i)
2871
2872                    IF ( match_lsm )  THEN
2873                       mm = surf_lsm_h%start_index(j,i)
2874                       vmea(l)%measured_vars_soil(m,n) = m_soil_h%var_2d(k,mm)
2875                    ENDIF
2876
2877                 ENDDO
2878
2879              CASE ( 'ts' ) ! surface temperature
2880                 DO  m = 1, vmea(l)%ns
2881!
2882!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
2883!--                 limit the indices.
2884                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2885                    j = MERGE( j           , nyn, j            < nyn )
2886                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2887                    i = MERGE( i           , nxr, i            < nxr )
2888
2889                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
2890                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%pt_surface(mm)
2891                    ENDDO
2892                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2893                       vmea(l)%measured_vars(m,n) = surf_lsm_h%pt_surface(mm)
2894                    ENDDO
2895                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
2896                       vmea(l)%measured_vars(m,n) = surf_usm_h%pt_surface(mm)
2897                    ENDDO
2898                 ENDDO
2899
2900              CASE ( 'lwp' ) ! liquid water path
2901                 IF ( ASSOCIATED( ql ) )  THEN
2902                    DO  m = 1, vmea(l)%ns
2903                       j = vmea(l)%j(m)
2904                       i = vmea(l)%i(m)
2905
2906                       vmea(l)%measured_vars(m,n) = SUM( ql(nzb:nzt,j,i) * dzw(1:nzt+1) )          &
2907                                                    * rho_surface
2908                    ENDDO
2909                 ENDIF
2910
2911              CASE ( 'ps' ) ! surface pressure
2912                 vmea(l)%measured_vars(:,n) = surface_pressure
2913
2914              CASE ( 'pswrtg' ) ! platform speed above ground
2915                 vmea(l)%measured_vars(:,n) = 0.0_wp
2916
2917              CASE ( 'pswrta' ) ! platform speed in air
2918                 vmea(l)%measured_vars(:,n) = 0.0_wp
2919
2920              CASE ( 't_lw' ) ! water temperature
2921                 DO  m = 1, vmea(l)%ns
2922!
2923!--                 Surface data is only available on inner subdomains, not
2924!--                 on ghost points. Hence, limit the indices.
2925                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
2926                    j = MERGE( j           , nyn, j            < nyn )
2927                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
2928                    i = MERGE( i           , nxr, i            < nxr )
2929
2930                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
2931                       IF ( surf_lsm_h%water_surface(m) )                                          &
2932                            vmea(l)%measured_vars(m,n) = t_soil_h%var_2d(nzt,m)
2933                    ENDDO
2934
2935                 ENDDO
2936!
2937!--           More will follow ...
2938              CASE ( 'ncaa' )
2939!
2940!--           No match found - just set a fill value
2941              CASE DEFAULT
2942                 vmea(l)%measured_vars(:,n) = vmea(l)%fillout
2943           END SELECT
2944
2945        ENDDO
2946
2947     ENDDO
2948
2949     CALL cpu_log( log_point_s(27), 'VM sampling', 'stop' )
2950
2951 END SUBROUTINE vm_sampling
2952
2953
2954 END MODULE virtual_measurement_mod
Note: See TracBrowser for help on using the repository browser.