Changeset 4498


Ignore:
Timestamp:
Apr 15, 2020 2:26:31 PM (4 years ago)
Author:
raasch
Message:

bugfix for creation of filetypes, argument removed from rd_mpi_io_open, files re-formatted to follow the PALM coding standard

Location:
palm/trunk/SOURCE
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/read_restart_data_mod.f90

    r4496 r4498  
    2525! -----------------
    2626! $Id$
     27! argument removed from rd_mpi_io_open
     28!
     29! 4496 2020-04-15 08:37:26Z raasch
    2730! bugfix: MPI barrier removed, coupling character added to input filename
    2831!
     
    845848!
    846849!--    Open the MPI-IO restart file.
    847        CALL rd_mpi_io_open( 'read', 'BININ' // TRIM( coupling_char ), only_global = .TRUE. )
     850       CALL rd_mpi_io_open( 'read', 'BININ' // TRIM( coupling_char ) )
    848851
    849852!
  • palm/trunk/SOURCE/restart_data_mpi_io_mod.f90

    r4497 r4498  
    2424! -----------------
    2525! $Id$
     26! bugfix for creation of filetypes, argument removed from rd_mpi_io_open
     27!
     28! 4497 2020-04-15 10:20:51Z raasch
    2629! last bugfix deactivated because of compile problems
    2730!
     
    244247!> Open restart file for read or write with MPI-IO
    245248!--------------------------------------------------------------------------------------------------!
    246  SUBROUTINE rd_mpi_io_open( action, file_name, only_global )
     249 SUBROUTINE rd_mpi_io_open( action, file_name )
    247250
    248251    IMPLICIT NONE
     
    251254    CHARACTER(LEN=*), INTENT(IN)  ::  file_name                        !<
    252255
    253     LOGICAL, INTENT(IN), OPTIONAL ::  only_global                      !<
    254     LOGICAL                       ::  set_filetype                     !<
    255 
    256256    INTEGER(iwp)                  ::  i                                !<
    257257    INTEGER(iwp)                  ::  gh_size                          !<
     
    276276!-- Create subarrays and file types
    277277    filetypes_created = .FALSE.
    278     set_filetype      = .TRUE.
    279 
    280     IF ( PRESENT( only_global ) )  THEN
    281        IF ( only_global )  set_filetype = .FALSE.
    282     ENDIF
    283278
    284279!
    285280!-- In case of read it is not known yet if data include total domain. Filetypes will be created
    286281!-- further below.
    287     IF ( set_filetype  .AND.  wr_flag)  THEN
     282    IF ( wr_flag)  THEN
    288283       CALL rs_mpi_io_create_filetypes
    289284       filetypes_created = .TRUE.
     
    368363
    369364!
    370 !--    File types deoend on if boundaries of the total domain is included in data
    371        IF ( set_filetype )  THEN
    372           CALL rs_mpi_io_create_filetypes
    373           filetypes_created = .TRUE.
    374        ENDIF
     365!--    File types depend on if boundaries of the total domain is included in data. This has been
     366!--    checked with the previous statement.
     367       CALL rs_mpi_io_create_filetypes
     368       filetypes_created = .TRUE.
    375369
    376370#if defined( __parallel )
  • palm/trunk/SOURCE/user_data_output_mask.f90

    r4360 r4498  
    11!> @file user_data_output_mask.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     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.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     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.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
    21 ! ------------------
     21! -----------------
    2222!
    2323!
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 4168 2019-08-16 13:50:17Z suehring
    30 ! Remove dependency on surface_mod + example for terrain-following output 
     34! Remove dependency on surface_mod + example for terrain-following output
    3135! adjusted
    32 ! 
     36!
    3337! 4069 2019-07-01 14:05:51Z Giersch
    34 ! Masked output running index mid has been introduced as a local variable to 
     38! Masked output running index mid has been introduced as a local variable to
    3539! avoid runtime error (Loop variable has been modified) in time_integration
    36 ! 
     40!
    3741! 3768 2019-02-27 14:35:58Z raasch
    3842! variables commented + statement added to avoid compiler warnings about unused variables
    39 ! 
     43!
    4044! 3655 2019-01-07 16:51:22Z knoop
    4145! Add terrain-following output
     
    4549! Description:
    4650! ------------
    47 !> Resorts the user-defined output quantity with indices (k,j,i) to a
    48 !> temporary array with indices (i,j,k) for masked data output.
    49 !------------------------------------------------------------------------------!
     51!> Resorts the user-defined output quantity with indices (k,j,i) to a temporary array with
     52!> indices (i,j,k) for masked data output.
     53!--------------------------------------------------------------------------------------------------!
    5054 SUBROUTINE user_data_output_mask( av, variable, found, local_pf, mid )
    51  
     55
    5256
    5357    USE control_parameters
    54        
     58
    5559    USE indices
    56    
     60
    5761    USE kinds
    58    
     62
    5963    USE user
    6064
    6165    IMPLICIT NONE
    6266
    63     CHARACTER (LEN=*) ::  variable  !<
     67    CHARACTER(LEN=*) ::  variable  !<
    6468
    65     INTEGER(iwp) ::  av             !<
    66     INTEGER(iwp) ::  mid            !< masked output running index
    67 !    INTEGER(iwp) ::  i              !<
    68 !    INTEGER(iwp) ::  j              !<
    69 !    INTEGER(iwp) ::  k              !<
    70 !    INTEGER(iwp) ::  topo_top_index !< k index of highest horizontal surface
     69    INTEGER(iwp) ::  av              !<
     70    INTEGER(iwp) ::  mid             !< masked output running index
     71!    INTEGER(iwp) ::  i               !<
     72!    INTEGER(iwp) ::  j               !<
     73!    INTEGER(iwp) ::  k               !<
     74!    INTEGER(iwp) ::  topo_top_index  !< k index of highest horizontal surface
    7175
    72     LOGICAL ::  found               !<
     76    LOGICAL ::  found  !<
    7377
    74     REAL(wp),                                                                  &
    75        DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  &
    76           local_pf   !<
     78    REAL(wp), DIMENSION(mask_size_l(mid,1),mask_size_l(mid,2),mask_size_l(mid,3)) ::  local_pf  !<
    7779
    7880!
     
    8789
    8890!--    Uncomment and extend the following lines, if necessary.
    89 !--    The arrays for storing the user defined quantities (here u2 and u2_av)
    90 !--    have to be declared and defined by the user!
     91!--    The arrays for storing the user defined quantities (here u2 and u2_av) have to be declared
     92!--    and defined by the user!
    9193!--    Sample for user-defined output:
    9294!       CASE ( 'u2' )
     
    98100!                   DO  j = 1, mask_size_l(mid,2)
    99101!                      DO  k = 1, mask_size_l(mid,3)
    100 !                         local_pf(i,j,k) = u2(mask_k(mid,k),                  &
    101 !                                              mask_j(mid,j),                  &
     102!                         local_pf(i,j,k) = u2(mask_k(mid,k),                                       &
     103!                                              mask_j(mid,j),                                       &
    102104!                                              mask_i(mid,i))
    103105!                      ENDDO
     
    111113!!
    112114!!--                   Get k index of highest horizontal surface
    113 !                      topo_top_index = topo_top_ind( &
    114 !                                        mask_j(mid,j), &
    115 !                                        mask_i(mid,i), &
    116 !                                        1          )
     115!                      topo_top_index = topo_top_ind( mask_j(mid,j), mask_i(mid,i), 1 )
    117116!!
    118117!!--                   Save output array
    119118!                      DO  k = 1, mask_size_l(mid,3)
    120 !                         local_pf(i,j,k) = u2(MIN( topo_top_index+mask_k(mid,k),&
    121 !                                                   nzt+1 ),                     &
    122 !                                              mask_j(mid,j),                    &
    123 !                                              mask_i(mid,i)                   )
     119!                         local_pf(i,j,k) = u2(MIN( topo_top_index + mask_k(mid,k), nzt+1 ),        &
     120!                                              mask_j(mid,j), mask_i(mid,i) )
    124121!                      ENDDO
    125122!                   ENDDO
     
    133130!                   DO  j = 1, mask_size_l(mid,2)
    134131!                      DO  k = 1, mask_size_l(mid,3)
    135 !                          local_pf(i,j,k) = u2_av(mask_k(mid,k),              &
    136 !                                                  mask_j(mid,j),              &
    137 !                                                  mask_i(mid,i) )
     132!                          local_pf(i,j,k) = u2_av(mask_k(mid,k), mask_j(mid,j), mask_i(mid,i) )
    138133!                       ENDDO
    139134!                    ENDDO
     
    146141!!
    147142!!--                   Get k index of highest horizontal surface
    148 !                      topo_top_index = topo_top_ind(   &
    149 !                                        mask_j(mid,j), &
    150 !                                        mask_i(mid,i), &
    151 !                                        1 )
     143!                      topo_top_index = topo_top_ind( mask_j(mid,j), mask_i(mid,i), 1 )
    152144!!
    153145!!--                   Save output array
    154146!                      DO  k = 1, mask_size_l(mid,3)
    155 !                         local_pf(i,j,k) = u2_av(                               &
    156 !                                              MIN( topo_top_index+mask_k(mid,k),&
    157 !                                                   nzt+1 ),                     &
    158 !                                              mask_j(mid,j),                    &
    159 !                                              mask_i(mid,i)                   )
     147!                         local_pf(i,j,k) = u2_av( MIN( topo_top_index+mask_k(mid,k), nzt+1 ),      &
     148!                                                  mask_j(mid,j), mask_i(mid,i) )
    160149!                      ENDDO
    161150!                   ENDDO
  • palm/trunk/SOURCE/user_flight.f90

    r4360 r4498  
    11!> @file user_flight.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     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.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     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.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
    21 ! ------------------
     21! -----------------
    2222!
    2323!
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 3768 2019-02-27 14:35:58Z raasch
    3034! unused variables commented out + statement added to avoid compiler warnings
    31 ! 
     35!
    3236! 3684 2019-01-20 20:20:58Z knoop
    3337! Corrected "Former revisions" section
    34 ! 
     38!
    3539! 1957 2016-07-07 10:43:48Z suehring
    3640! Initial revision
     
    3842! Description:
    3943! ------------
    40 !> Calculation of user-defined output quantity for flight measurements after
    41 !> each timestep.
    42 !------------------------------------------------------------------------------!
     44!> Calculation of user-defined output quantity for flight measurements after each timestep.
     45!--------------------------------------------------------------------------------------------------!
    4346 SUBROUTINE user_flight( var, id )
    4447
    4548    USE control_parameters
    46    
     49
    4750    USE grid_variables
    4851
     
    6063!    INTEGER(iwp) ::  j  !< index along y
    6164!    INTEGER(iwp) ::  k  !< index along z
    62     INTEGER(iwp) ::  id !< variable identifyer, according to the settings in user_init_flight
    63        
    64     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var !< treated variable
     65    INTEGER(iwp) ::  id  !< variable identifyer, according to the settings in user_init_flight
     66
     67    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !< treated variable
    6568
    6669!
     
    6972
    7073!
    71 !-- Here, the respective variable is calculated. There is no call of
    72 !-- exchange_horiz necessary.
    73 !-- The variable identifyer (id) must be set according to the settings in
    74 !-- user_init_flight.
     74!-- Here, the respective variable is calculated. There is no call of exchange_horiz necessary.
     75!-- The variable identifyer (id) must be set according to the settings in user_init_flight.
    7576!-- Please note, so far, variable must be located at the center of a grid box.
    7677!     var = 0.0_wp
    7778
    7879!     SELECT CASE ( id )
    79 ! 
     80!
    8081!        CASE ( 1 )
    81 !           DO i = nxl-1, nxr+1
    82 !              DO j = nys-1, nyn+1
    83 !                 DO k = nzb, nzt
     82!           DO  i = nxl-1, nxr+1
     83!              DO  j = nys-1, nyn+1
     84!                 DO  k = nzb, nzt
    8485!                    var(k,j,i) = ABS( u(k,j,i )
    8586!                 ENDDO
    8687!              ENDDO
    8788!           ENDDO
    88 !           
     89!
    8990!        CASE ( 2 )
    90 !           DO i = nxl-1, nxr+1
    91 !              DO j = nys-1, nyn+1
    92 !                 DO k = nzb, nzt
     91!           DO  i = nxl-1, nxr+1
     92!              DO  j = nys-1, nyn+1
     93!                 DO  k = nzb, nzt
    9394!                    var(k,j,i) = ABS( v(k,j,i) )
    9495!                 ENDDO
    9596!              ENDDO
    9697!           ENDDO
    97 ! 
     98!
    9899!     END SELECT
    99100
  • palm/trunk/SOURCE/user_init_3d_model.f90

    r4360 r4498  
    11!> @file user_init_3d_model.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     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.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     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.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 3768 2019-02-27 14:35:58Z raasch
    3034! variables commented out to avoid compiler warnings about unused variables
    31 ! 
     35!
    3236! 3655 2019-01-07 16:51:22Z knoop
    3337! Corrected "Former revisions" section
     
    4246!> @attention The user is responsible to set at least all those quantities which
    4347!>            are normally set within init_3d_model!
    44 !------------------------------------------------------------------------------!
     48!--------------------------------------------------------------------------------------------------!
    4549 SUBROUTINE user_init_3d_model
    46  
     50
    4751
    4852    USE arrays_3d
    49    
     53
    5054    USE control_parameters
    51    
     55
    5256    USE indices
    53    
     57
    5458    USE kinds
    5559
    5660    USE surface_mod
    57    
     61
    5862    USE user
    5963
    6064    IMPLICIT NONE
    6165
    62 !    INTEGER(iwp) ::  l !< running index surface orientation
    63 !    INTEGER(iwp) ::  m !< running index surface elements
     66!    INTEGER(iwp) ::  l  !< running index surface orientation
     67!    INTEGER(iwp) ::  m  !< running index surface elements
    6468
    6569!
    6670!-- Initialization of surface-related quantities.
    67 !-- The following example shows required initialization of surface quantitites
    68 !-- at default-type upward-facing surfaces. 
     71!-- The following example shows required initialization of surface quantitites at default-type
     72!-- upward-facing surfaces.
    6973!   DO  m = 1, surf_def_h(0)%ns
    7074!      surf_def_h(0)%ol(m)   = ...    ! Obukhov length
     
    8791!         surf_def_h(0)%ssws(m) = ... ! surface latent heat flux
    8892!      ENDIF
    89 !   ENDDO 
     93!   ENDDO
    9094!
    9195!-- Same for natural and urban type surfaces
    9296!   DO  m = 1, surf_lsm_h%ns
    9397!      ...
    94 !   ENDDO 
     98!   ENDDO
    9599!   DO  m = 1, surf_usm_h%ns
    96100!      ...
    97101!   ENDDO
    98102!
    99 !-- Also care for vertically aligned surfaces (default-, natural-, and 
     103!-- Also care for vertically aligned surfaces (default-, natural-, and
    100104!-- urban-type).
    101105!   DO  l = 0, 3
  • palm/trunk/SOURCE/user_init_flight.f90

    r4360 r4498  
    11!> @file user_init_flight.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     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.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     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.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 3768 2019-02-27 14:35:58Z raasch
    3034! statements commented or added to avoid compiler warnings about unused variables
    31 ! 
     35!
    3236! 3655 2019-01-07 16:51:22Z knoop
    3337! Corrected "Former revisions" section
    34 ! 
     38!
    3539! 1957 2016-07-07 10:43:48Z suehring
    3640! Initial revision
     
    3943! ------------
    4044!> Execution of user-defined initialization for flight measurements.
    41 !------------------------------------------------------------------------------!
     45!--------------------------------------------------------------------------------------------------!
    4246 SUBROUTINE user_init_flight( init, k, id, label_leg )
    43  
     47
    4448
    4549    USE control_parameters
    46    
     50
    4751    USE indices
    48    
     52
    4953    USE kinds
    50    
    51 !    USE netcdf_interface,                                                      &
    52 !        ONLY: dofl_label, dofl_unit
    53    
     54
     55!    USE netcdf_interface,                                                                          &
     56!        ONLY: dofl_label,                                                                          &
     57!              dofl_unit
     58
    5459    USE user
    5560
    5661    IMPLICIT NONE
    57    
     62
    5863    CHARACTER(LEN=10), OPTIONAL ::  label_leg     !< label of the respective leg
    59    
     64
    6065    INTEGER(iwp), OPTIONAL                ::  id  !< variable index
    6166    INTEGER(iwp), OPTIONAL, INTENT(INOUT) ::  k   !< index for respective variable and leg
    62    
    63     LOGICAL ::  init  !< variable to recognize initial call 
     67
     68    LOGICAL ::  init  !< variable to recognize initial call
    6469
    6570!
     
    7176!
    7277!-- Sample for user-defined flight-time series.
    73 !-- For each quantity you have to give a label and a unit, which will be used
    74 !-- for the output into NetCDF file. They must not contain more than
    75 !-- twenty characters.
     78!-- For each quantity you have to give a label and a unit, which will be used for the output into
     79!-- NetCDF file. They must not contain more than twenty characters.
    7680
    7781
     
    8084!--    The number of user-defined quantity has to be increased appropriately.
    8185!--    In the following example, 2 user-defined quantities are added.
    82 !        num_var_fl_user = num_var_fl_user + 2 
     86!        num_var_fl_user = num_var_fl_user + 2
    8387
    8488       init = .FALSE.
    85    
     89
    8690    ELSE
    87    
     91
    8892!
    8993!--    Please add the respective number of new variables as following:
    90      
     94
    9195!        SELECT CASE ( id )
    92 !       
     96!
    9397!           CASE ( 1 )
    9498!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_u'
    9599!              dofl_unit(k)    = 'm/s'
    96100!              k               = k + 1
    97 !             
     101!
    98102!           CASE ( 2 )
    99 !     
     103!
    100104!              dofl_label(k)   = TRIM(label_leg) // '_' // 'abs_v'
    101105!              dofl_unit(k)    = 'm/s'
    102106!              k               = k + 1
    103 !             
     107!
    104108!        END SELECT
    105109
    106110    ENDIF
    107        
     111
    108112 END SUBROUTINE user_init_flight
    109113
  • palm/trunk/SOURCE/user_init_grid.f90

    r4360 r4498  
    11!> @file user_init_grid.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     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.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     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.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 3768 2019-02-27 14:35:58Z raasch
    3034! variables commented + statement added to avoid compiler warnings about unused variables
    31 ! 
     35!
    3236! 3655 2019-01-07 16:51:22Z knoop
    3337! dz was replaced by dz(1)
     
    4044! ------------
    4145!> Execution of user-defined grid initializing actions
    42 !------------------------------------------------------------------------------!
     46!--------------------------------------------------------------------------------------------------!
    4347 SUBROUTINE user_init_grid( topo_3d )
    44  
     48
    4549
    4650    USE control_parameters
    47    
     51
    4852    USE indices
    49    
     53
    5054    USE kinds
    51    
     55
    5256    USE user
    5357
    5458    IMPLICIT NONE
    5559
    56 !    INTEGER(iwp)                                           ::  k_topo      !< topography top index
    57     INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d     !< 3D topography field
     60!    INTEGER(iwp)                                           ::  k_topo   !< topography top index
     61    INTEGER(iwp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  topo_3d  !< 3D topography field
    5862
    5963!    REAL(wp) ::  h_topo !< user-defined topography height
     
    7882       CASE ( 'user_defined_topography_1' )
    7983!
    80 !--       Here the user can define his own topography.
     84!--       Here the user can define their own topography.
    8185!--       After definition, please remove the following three lines!
    8286          message_string = 'topography "' // topography // '" not available yet'
    8387          CALL message( 'user_init_grid', 'UI0005', 1, 2, 0, 6, 0 )
    8488!
    85 !--       The user is allowed to set surface-mounted as well as non-surface
    86 !--       mounted topography (e.g. overhanging structures). For both, use
    87 !--       3D array topo_3d and set bit 0. The convention is: bit is zero inside
    88 !--       topography, bit is 1 for atmospheric grid point.
    89 !--       The following example shows how to prescribe sine-like topography
    90 !--       along x-direction with amplitude of 10 * dz(1) and wavelength 10 * dy.
     89!--       The user is allowed to set surface-mounted as well as non-surface mounted topography
     90!--       (e.g. overhanging structures). For both, use 3D array topo_3d and set bit 0. The
     91!--       convention is: bit is zero inside topography, bit is 1 for atmospheric grid point.
     92!--       The following example shows how to prescribe sine-like topography along x-direction with
     93!--       amplitude of 10 * dz(1) and wavelength 10 * dy.
    9194!           DO  i = nxlg, nxrg
    92 !              h_topo = 10.0_wp * dz(1) * (SIN(3.14_wp*0.5_wp)*i*dx / ( 5.0_wp * dy ) )**2
    93 ! 
     95!              h_topo = 10.0_wp * dz(1) * ( SIN( 3.14_wp * 0.5_wp) * i * dx / ( 5.0_wp * dy ) )**2
     96!
    9497!              k_topo = MINLOC( ABS( zw - h_topo ), 1 ) - 1
    95 !
    96 !              topo_3d(k_topo+1:nzt+1,:,i) =                                     &
    97 !                                          IBSET( topo_3d(k_topo+1:nzt+1,:,i), 0 )
    98 !           ENDDO
    99 !
     98!
     99!              topo_3d(k_topo+1:nzt+1,:,i) = IBSET( topo_3d(k_topo+1:nzt+1,:,i), 0 )
     100!           ENDDO
     101!
    100102!           CALL exchange_horiz_int( topo_3d, nys, nyn, nxl, nxr, nzt, nbgp )
    101103
    102104       CASE DEFAULT
    103105!
    104 !--       The DEFAULT case is reached if the parameter topography contains a
    105 !--       wrong character string that is neither recognized in init_grid nor
    106 !--       here in user_init_grid.
     106!--       The DEFAULT case is reached if the parameter topography contains a wrong character string
     107!--       that is neither recognized in init_grid nor here in user_init_grid.
    107108          message_string = 'unknown topography "' // topography // '"'
    108109          CALL message( 'user_init_grid', 'UI0006', 1, 2, 0, 6, 0 )
     
    110111    END SELECT
    111112
    112 
    113 
    114 
    115113 END SUBROUTINE user_init_grid
    116114
  • palm/trunk/SOURCE/virtual_measurement_mod.f90

    r4481 r4498  
    11!> @virtual_measurement_mod.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
    9 !
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    13 !
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
    16 !
    17 ! Copyright 2017-2020 iz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     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!
    1919!
    2020! Current revisions:
     
    2525! -----------------
    2626! $Id$
     27! file re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4481 2020-03-31 18:55:54Z maronga
    2731! bugfix: cpp-directives for serial mode added
    28 ! 
     32!
    2933! 4438 2020-03-03 20:49:28Z suehring
    3034! Add cpu-log points
    31 ! 
     35!
    3236! 4422 2020-02-24 22:45:13Z suehring
    3337! Missing trim()
    34 ! 
     38!
    3539! 4408 2020-02-14 10:04:39Z gronemeier
    3640! - Output of character string station_name after DOM has been enabled to
    3741!   output character variables
    3842! - Bugfix, missing coupling_char statement when opening the input file
    39 ! 
     43!
    4044! 4408 2020-02-14 10:04:39Z gronemeier
    4145! write fill_value attribute
     
    116120! Description:
    117121! ------------
    118 !> The module acts as an interface between 'real-world' observations and
    119 !> model simulations. Virtual measurements will be taken in the model at the
    120 !> coordinates representative for the 'real-world' observation coordinates.
    121 !> More precisely, coordinates and measured quanties will be read from a
    122 !> NetCDF file which contains all required information. In the model,
    123 !> the same quantities (as long as all the required components are switched-on)
    124 !> will be sampled at the respective positions and output into an extra file,
    125 !> which allows for straight-forward comparison of model results with
    126 !> observations.
    127 !------------------------------------------------------------------------------!
     122!> The module acts as an interface between 'real-world' observations and model simulations.
     123!> Virtual measurements will be taken in the model at the coordinates representative for the
     124!> 'real-world' observation coordinates. More precisely, coordinates and measured quanties will be
     125!> read from a NetCDF file which contains all required information. In the model, the same
     126!> quantities (as long as all the required components are switched-on) will be sampled at the
     127!> respective positions and output into an extra file, which allows for straight-forward comparison
     128!> of model results with observations.
     129!--------------------------------------------------------------------------------------------------!
    128130 MODULE virtual_measurement_mod
    129131
    130     USE arrays_3d,                                                             &
    131         ONLY:  dzw,                                                            &
    132                exner,                                                          &
    133                hyp,                                                            &
    134                q,                                                              &
    135                ql,                                                             &
    136                pt,                                                             &
    137                rho_air,                                                        &
    138                u,                                                              &
    139                v,                                                              &
    140                w,                                                              &
    141                zu,                                                             &
     132    USE arrays_3d,                                                                                 &
     133        ONLY:  dzw,                                                                                &
     134               exner,                                                                              &
     135               hyp,                                                                                &
     136               q,                                                                                  &
     137               ql,                                                                                 &
     138               pt,                                                                                 &
     139               rho_air,                                                                            &
     140               u,                                                                                  &
     141               v,                                                                                  &
     142               w,                                                                                  &
     143               zu,                                                                                 &
    142144               zw
    143145
    144     USE basic_constants_and_equations_mod,                                     &
    145         ONLY:  convert_utm_to_geographic,                                      &
    146                degc_to_k,                                                      &
    147                magnus,                                                         &
    148                pi,                                                             &
     146    USE basic_constants_and_equations_mod,                                                         &
     147        ONLY:  convert_utm_to_geographic,                                                          &
     148               degc_to_k,                                                                          &
     149               magnus,                                                                             &
     150               pi,                                                                                 &
    149151               rd_d_rv
    150152
    151     USE chem_gasphase_mod,                                                     &
     153    USE chem_gasphase_mod,                                                                         &
    152154        ONLY:  nvar
    153155
    154     USE chem_modules,                                                          &
     156    USE chem_modules,                                                                              &
    155157        ONLY:  chem_species
    156158
    157     USE control_parameters,                                                    &
    158         ONLY:  air_chemistry,                                                  &
    159                coupling_char,                                                  &
    160                dz,                                                             &
    161                end_time,                                                       &
    162                humidity,                                                       &
    163                message_string,                                                 &
    164                neutral,                                                        &
    165                origin_date_time,                                               &
    166                rho_surface,                                                    &
    167                surface_pressure,                                               &
    168                time_since_reference_point,                                     &
     159    USE control_parameters,                                                                        &
     160        ONLY:  air_chemistry,                                                                      &
     161               coupling_char,                                                                      &
     162               dz,                                                                                 &
     163               end_time,                                                                           &
     164               humidity,                                                                           &
     165               message_string,                                                                     &
     166               neutral,                                                                            &
     167               origin_date_time,                                                                   &
     168               rho_surface,                                                                        &
     169               surface_pressure,                                                                   &
     170               time_since_reference_point,                                                         &
    169171               virtual_measurement
    170172
    171     USE cpulog,                                                                &
    172         ONLY:  cpu_log,                                                        &
     173    USE cpulog,                                                                                    &
     174        ONLY:  cpu_log,                                                                            &
    173175               log_point_s
    174176
    175177    USE data_output_module
    176178
    177     USE grid_variables,                                                        &
    178         ONLY:  ddx,                                                            &
    179                ddy,                                                            &
    180                dx,                                                             &
     179    USE grid_variables,                                                                            &
     180        ONLY:  ddx,                                                                                &
     181               ddy,                                                                                &
     182               dx,                                                                                 &
    181183               dy
    182184
    183     USE indices,                                                               &
    184         ONLY:  nbgp,                                                           &
    185                nzb,                                                            &
    186                nzt,                                                            &
    187                nxl,                                                            &
    188                nxlg,                                                           &
    189                nxr,                                                            &
    190                nxrg,                                                           &
    191                nys,                                                            &
    192                nysg,                                                           &
    193                nyn,                                                            &
    194                nyng,                                                           &
    195                topo_top_ind,                                                   &
     185    USE indices,                                                                                   &
     186        ONLY:  nbgp,                                                                               &
     187               nzb,                                                                                &
     188               nzt,                                                                                &
     189               nxl,                                                                                &
     190               nxlg,                                                                               &
     191               nxr,                                                                                &
     192               nxrg,                                                                               &
     193               nys,                                                                                &
     194               nysg,                                                                               &
     195               nyn,                                                                                &
     196               nyng,                                                                               &
     197               topo_top_ind,                                                                       &
    196198               wall_flags_total_0
    197199
    198200    USE kinds
    199201
    200     USE netcdf_data_input_mod,                                                 &
    201         ONLY:  close_input_file,                                               &
    202                coord_ref_sys,                                                  &
    203                crs_list,                                                       &
    204                get_attribute,                                                  &
    205                get_dimension_length,                                           &
    206                get_variable,                                                   &
    207                init_model,                                                     &
    208                input_file_atts,                                                &
    209                input_file_vm,                                                  &
    210                input_pids_static,                                              &
    211                input_pids_vm,                                                  &
    212                inquire_fill_value,                                             &
    213                open_read_file,                                                 &
     202    USE netcdf_data_input_mod,                                                                     &
     203        ONLY:  close_input_file,                                                                   &
     204               coord_ref_sys,                                                                      &
     205               crs_list,                                                                           &
     206               get_attribute,                                                                      &
     207               get_dimension_length,                                                               &
     208               get_variable,                                                                       &
     209               init_model,                                                                         &
     210               input_file_atts,                                                                    &
     211               input_file_vm,                                                                      &
     212               input_pids_static,                                                                  &
     213               input_pids_vm,                                                                      &
     214               inquire_fill_value,                                                                 &
     215               open_read_file,                                                                     &
    214216               pids_id
    215217
    216218    USE pegrid
    217219
    218     USE surface_mod,                                                           &
    219         ONLY:  surf_lsm_h,                                                     &
     220    USE surface_mod,                                                                               &
     221        ONLY:  surf_lsm_h,                                                                         &
    220222               surf_usm_h
    221223
    222     USE land_surface_model_mod,                                                &
    223         ONLY:  m_soil_h,                                                       &
    224                nzb_soil,                                                       &
    225                nzt_soil,                                                       &
    226                t_soil_h,                                                       &
     224    USE land_surface_model_mod,                                                                    &
     225        ONLY:  m_soil_h,                                                                           &
     226               nzb_soil,                                                                           &
     227               nzt_soil,                                                                           &
     228               t_soil_h,                                                                           &
    227229               zs
    228230
    229     USE radiation_model_mod,                                                   &
    230         ONLY:  rad_lw_in,                                                      &
    231                rad_lw_out,                                                     &
    232                rad_sw_in,                                                      &
    233                rad_sw_in_diff,                                                 &
    234                rad_sw_out,                                                     &
     231    USE radiation_model_mod,                                                                       &
     232        ONLY:  rad_lw_in,                                                                          &
     233               rad_lw_out,                                                                         &
     234               rad_sw_in,                                                                          &
     235               rad_sw_in_diff,                                                                     &
     236               rad_sw_out,                                                                         &
    235237               radiation_scheme
    236238
    237     USE urban_surface_mod,                                                     &
    238         ONLY:  nzb_wall,                                                       &
    239                nzt_wall,                                                       &
     239    USE urban_surface_mod,                                                                         &
     240        ONLY:  nzb_wall,                                                                           &
     241               nzt_wall,                                                                           &
    240242               t_wall_h
    241243
     
    244246
    245247    TYPE virt_general
    246        INTEGER(iwp) ::  nvm = 0   !< number of virtual measurements
     248       INTEGER(iwp) ::  nvm = 0  !< number of virtual measurements
    247249    END TYPE virt_general
    248250
    249251    TYPE virt_var_atts
    250        CHARACTER(LEN=100) ::  coordinates          !< defined longname of the variable
    251        CHARACTER(LEN=100) ::  grid_mapping         !< defined longname of the variable
    252        CHARACTER(LEN=100) ::  long_name            !< defined longname of the variable
    253        CHARACTER(LEN=100) ::  name                 !< variable name
    254        CHARACTER(LEN=100) ::  standard_name        !< defined standard name of the variable
    255        CHARACTER(LEN=100) ::  units                !< unit of the output variable
    256 
    257        REAL(wp)           ::  fill_value = -9999.0 !< _FillValue attribute
     252       CHARACTER(LEN=100) ::  coordinates           !< defined longname of the variable
     253       CHARACTER(LEN=100) ::  grid_mapping          !< defined longname of the variable
     254       CHARACTER(LEN=100) ::  long_name             !< defined longname of the variable
     255       CHARACTER(LEN=100) ::  name                  !< variable name
     256       CHARACTER(LEN=100) ::  standard_name         !< defined standard name of the variable
     257       CHARACTER(LEN=100) ::  units                 !< unit of the output variable
     258
     259       REAL(wp)           ::  fill_value = -9999.0  !< _FillValue attribute
    258260    END TYPE virt_var_atts
    259261
    260262    TYPE virt_mea
    261 
    262        CHARACTER(LEN=100)  ::  feature_type                     !< type of the real-world measurement
    263        CHARACTER(LEN=100)  ::  feature_type_out = 'timeSeries'  !< type of the virtual measurement
    264                                                                 !< (all will be timeSeries, even trajectories)
    265        CHARACTER(LEN=100)  ::  nc_filename                      !< name of the NetCDF output file for the station
    266        CHARACTER(LEN=100)  ::  site                             !< name of the measurement site
    267 
    268        CHARACTER(LEN=1000) ::  data_content = REPEAT(' ', 1000) !< string of measured variables (data output only)
    269 
    270        INTEGER(iwp) ::  end_coord_a = 0     !< end coordinate in NetCDF file for local atmosphere observations
    271        INTEGER(iwp) ::  end_coord_s = 0     !< end coordinate in NetCDF file for local soil observations
    272        INTEGER(iwp) ::  file_time_index = 0 !< time index in NetCDF output file
    273        INTEGER(iwp) ::  ns = 0              !< number of observation coordinates on subdomain, for atmospheric measurements
    274        INTEGER(iwp) ::  ns_tot = 0          !< total number of observation coordinates, for atmospheric measurements
    275        INTEGER(iwp) ::  n_tr_st             !< number of trajectories / station of a measurement
    276        INTEGER(iwp) ::  nmeas               !< number of measured variables (atmosphere + soil)
    277        INTEGER(iwp) ::  ns_soil = 0         !< number of observation coordinates on subdomain, for soil measurements
    278        INTEGER(iwp) ::  ns_soil_tot = 0     !< total number of observation coordinates, for soil measurements
    279        INTEGER(iwp) ::  start_coord_a = 0   !< start coordinate in NetCDF file for local atmosphere observations
    280        INTEGER(iwp) ::  start_coord_s = 0   !< start coordinate in NetCDF file for local soil observations
    281 
    282        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  dim_t !< number observations individual for each trajectory
    283                                                          !< or station that are no _FillValues
     263       CHARACTER(LEN=100)  ::  feature_type                      !< type of the real-world measurement
     264       CHARACTER(LEN=100)  ::  feature_type_out = 'timeSeries'   !< type of the virtual measurement
     265                                                                 !< (all will be timeSeries, even trajectories)
     266       CHARACTER(LEN=100)  ::  nc_filename                       !< name of the NetCDF output file for the station
     267       CHARACTER(LEN=100)  ::  site                              !< name of the measurement site
     268
     269       CHARACTER(LEN=1000) ::  data_content = REPEAT(' ', 1000)  !< string of measured variables (data output only)
     270
     271       INTEGER(iwp) ::  end_coord_a     = 0  !< end coordinate in NetCDF file for local atmosphere observations
     272       INTEGER(iwp) ::  end_coord_s     = 0  !< end coordinate in NetCDF file for local soil observations
     273       INTEGER(iwp) ::  file_time_index = 0  !< time index in NetCDF output file
     274       INTEGER(iwp) ::  ns              = 0  !< number of observation coordinates on subdomain, for atmospheric measurements
     275       INTEGER(iwp) ::  ns_tot          = 0  !< total number of observation coordinates, for atmospheric measurements
     276       INTEGER(iwp) ::  n_tr_st              !< number of trajectories / station of a measurement
     277       INTEGER(iwp) ::  nmeas                !< number of measured variables (atmosphere + soil)
     278       INTEGER(iwp) ::  ns_soil         = 0  !< number of observation coordinates on subdomain, for soil measurements
     279       INTEGER(iwp) ::  ns_soil_tot     = 0  !< total number of observation coordinates, for soil measurements
     280       INTEGER(iwp) ::  start_coord_a   = 0  !< start coordinate in NetCDF file for local atmosphere observations
     281       INTEGER(iwp) ::  start_coord_s   = 0  !< start coordinate in NetCDF file for local soil observations
     282
     283       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  dim_t  !< number observations individual for each trajectory
     284                                                          !< or station that are no _FillValues
    284285
    285286       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  i       !< grid index for measurement position in x-direction
     
    291292       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_soil  !< grid index for measurement position in k-direction
    292293
    293        LOGICAL ::  trajectory         = .FALSE. !< flag indicating that the observation is a mobile observation
    294        LOGICAL ::  timseries          = .FALSE. !< flag indicating that the observation is a stationary point measurement
    295        LOGICAL ::  timseries_profile  = .FALSE. !< flag indicating that the observation is a stationary profile measurement
    296        LOGICAL ::  soil_sampling      = .FALSE. !< flag indicating that soil state variables were sampled
    297 
    298        REAL(wp) ::  fill_eutm                            !< fill value for UTM coordinates in case of missing values
    299        REAL(wp) ::  fill_nutm                            !< fill value for UTM coordinates in case of missing values
    300        REAL(wp) ::  fill_zar                             !< fill value for heigth coordinates in case of missing values
    301        REAL(wp) ::  fillout = -9999.0                    !< fill value for output in case a observation is taken
    302                                                          !< e.g. from inside a building
    303        REAL(wp) ::  origin_x_obs                         !< origin of the observation in UTM coordiates in x-direction
    304        REAL(wp) ::  origin_y_obs                         !< origin of the observation in UTM coordiates in y-direction
    305 
     294       LOGICAL ::  soil_sampling      = .FALSE.  !< flag indicating that soil state variables were sampled
     295       LOGICAL ::  trajectory         = .FALSE.  !< flag indicating that the observation is a mobile observation
     296       LOGICAL ::  timseries          = .FALSE.  !< flag indicating that the observation is a stationary point measurement
     297       LOGICAL ::  timseries_profile  = .FALSE.  !< flag indicating that the observation is a stationary profile measurement
     298
     299       REAL(wp) ::  fill_eutm          !< fill value for UTM coordinates in case of missing values
     300       REAL(wp) ::  fill_nutm          !< fill value for UTM coordinates in case of missing values
     301       REAL(wp) ::  fill_zar           !< fill value for heigth coordinates in case of missing values
     302       REAL(wp) ::  fillout = -9999.0  !< fill value for output in case an observation is taken e.g. from inside a building
     303       REAL(wp) ::  origin_x_obs       !< origin of the observation in UTM coordiates in x-direction
     304       REAL(wp) ::  origin_y_obs       !< origin of the observation in UTM coordiates in y-direction
     305
     306       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  depth         !< measurement depth in soil
    306307       REAL(wp), DIMENSION(:), ALLOCATABLE   ::  zar           !< measurement height above ground level
    307        REAL(wp), DIMENSION(:), ALLOCATABLE   ::  depth         !< measurement depth in soil
    308308
    309309       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  measured_vars       !< measured variables
     
    311311
    312312       TYPE( virt_var_atts ), DIMENSION(:), ALLOCATABLE ::  var_atts !< variable attributes
    313 
    314313    END TYPE virt_mea
    315314
    316     CHARACTER(LEN=5)  ::  char_eutm = "E_UTM"                      !< dimension name for UTM coordinate easting
    317     CHARACTER(LEN=11) ::  char_feature = "featureType"             !< attribute name for feature type
     315    CHARACTER(LEN=5)  ::  char_eutm = "E_UTM"            !< dimension name for UTM coordinate easting
     316    CHARACTER(LEN=11) ::  char_feature = "featureType"   !< attribute name for feature type
    318317
    319318    ! This need to be generalized
    320319    CHARACTER(LEN=10) ::  char_fill = '_FillValue'                 !< attribute name for fill value
    321320    CHARACTER(LEN=9)  ::  char_long = 'long_name'                  !< attribute name for long_name
    322     CHARACTER(LEN=13) ::  char_standard = 'standard_name'          !< attribute name for standard_name
    323     CHARACTER(LEN=5)  ::  char_unit = 'units'                      !< attribute name for standard_name
    324     CHARACTER(LEN=11) ::  char_soil = "soil_sample"                !< attribute name for soil sampling indication
    325321    CHARACTER(LEN=18) ::  char_mv = "measured_variables"           !< variable name for the array with the measured variable names
    326322    CHARACTER(LEN=5)  ::  char_nutm = "N_UTM"                      !< dimension name for UTM coordinate northing
     
    329325    CHARACTER(LEN=8)  ::  char_origy = "origin_y"                  !< attribute name for station coordinate in y
    330326    CHARACTER(LEN=4)  ::  char_site = "site"                       !< attribute name for site name
     327    CHARACTER(LEN=11) ::  char_soil = "soil_sample"                !< attribute name for soil sampling indication
     328    CHARACTER(LEN=13) ::  char_standard = 'standard_name'          !< attribute name for standard_name
    331329    CHARACTER(LEN=9)  ::  char_station_h = "station_h"             !< variable name indicating height of the site
     330    CHARACTER(LEN=5)  ::  char_unit = 'units'                      !< attribute name for standard_name
    332331    CHARACTER(LEN=1)  ::  char_zar = "z"                           !< attribute name indicating height above reference level
    333332    CHARACTER(LEN=10) ::  type_ts   = 'timeSeries'                 !< name of stationary point measurements
     
    335334    CHARACTER(LEN=17) ::  type_tspr = 'timeSeriesProfile'          !< name of stationary profile measurements
    336335
    337     CHARACTER(LEN=6), DIMENSION(1:5) ::  soil_vars       = (/                  & !< list of soil variables
    338                             't_soil',                                          &
    339                             'm_soil',                                          &
    340                             'lwc   ',                                          &
    341                             'lwcs  ',                                          &
    342                             'smp   '                       /)
    343 
    344     CHARACTER(LEN=10), DIMENSION(0:1,1:8) ::  chem_vars = RESHAPE( (/          &
    345                                               'mcpm1     ', 'PM1       ',      &
    346                                               'mcpm2p5   ', 'PM2.5     ',      &
    347                                               'mcpm10    ', 'PM10      ',      &
    348                                               'mfno2     ', 'NO2       ',      &
    349                                               'mfno      ', 'NO        ',      &
    350                                               'mcno2     ', 'NO2       ',      &
    351                                               'mcno      ', 'NO        ',      &
    352                                               'tro3      ', 'O3        '       &
    353                                                                    /), (/ 2, 8 /) )
    354 
    355     LOGICAL ::  global_attribute = .TRUE.           !< flag indicating a global attribute
    356     LOGICAL ::  initial_write_coordinates = .FALSE. !< flag indicating a global attribute
    357     LOGICAL ::  use_virtual_measurement = .FALSE.   !< Namelist parameter
    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 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 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 neighboring grid points (in each direction) where virtual trajectory
    366                                               !< measurements shall be taken, in addition to the given coordinates in the driver
    367 
    368     REAL(wp) ::  dt_virtual_measurement = 0.0_wp    !< sampling interval
     336    CHARACTER(LEN=6), DIMENSION(1:5) ::  soil_vars = (/ 't_soil', & !< list of soil variables
     337                                                        'm_soil',                                  &
     338                                                        'lwc   ',                                  &
     339                                                        'lwcs  ',                                  &
     340                                                        'smp   ' /)
     341
     342    CHARACTER(LEN=10), DIMENSION(0:1,1:8) ::  chem_vars = RESHAPE( (/ 'mcpm1     ', 'PM1       ',  &
     343                                                                      'mcpm2p5   ', 'PM2.5     ',  &
     344                                                                      'mcpm10    ', 'PM10      ',  &
     345                                                                      'mfno2     ', 'NO2       ',  &
     346                                                                      'mfno      ', 'NO        ',  &
     347                                                                      'mcno2     ', 'NO2       ',  &
     348                                                                      'mcno      ', 'NO        ',  &
     349                                                                      'tro3      ', 'O3        '   &
     350                                                                    /), (/ 2, 8 /) )
     351
     352    INTEGER(iwp) ::  maximum_name_length = 32  !< maximum name length of station names
     353    INTEGER(iwp) ::  ntimesteps                !< number of timesteps defined in NetCDF output file
     354    INTEGER(iwp) ::  off_pr              = 1   !< number of neighboring grid points (in each direction) where virtual profile
     355                                               !< measurements shall be taken, in addition to the given coordinates in the driver
     356    INTEGER(iwp) ::  off_ts              = 1   !< number of neighboring grid points (in each direction) where virtual timeseries
     357                                               !< measurements shall be taken, in addition to the given coordinates in the driver
     358    INTEGER(iwp) ::  off_tr              = 1   !< number of neighboring grid points (in each direction) where virtual trajectory
     359                                               !< measurements shall be taken, in addition to the given coordinates in the driver
     360    LOGICAL ::  global_attribute          = .TRUE.   !< flag indicating a global attribute
     361    LOGICAL ::  initial_write_coordinates = .FALSE.  !< flag indicating a global attribute
     362    LOGICAL ::  use_virtual_measurement   = .FALSE.  !< Namelist parameter
     363
     364    REAL(wp) ::  dt_virtual_measurement   = 0.0_wp  !< sampling interval
    369365    REAL(wp) ::  time_virtual_measurement = 0.0_wp  !< time since last sampling
    370     REAL(wp) ::  vm_time_start = 0.0                !< time after which sampling shall start
    371 
    372     TYPE( virt_general )                        ::  vmea_general !< data structure which encompass global variables
    373     TYPE( virt_mea ), DIMENSION(:), ALLOCATABLE ::  vmea         !< data structure contain station-specific variables
     366    REAL(wp) ::  vm_time_start            = 0.0     !< time after which sampling shall start
     367
     368    TYPE( virt_general )                        ::  vmea_general  !< data structure which encompasses global variables
     369    TYPE( virt_mea ), DIMENSION(:), ALLOCATABLE ::  vmea          !< data structure containing station-specific variables
    374370
    375371    INTERFACE vm_check_parameters
     
    403399!
    404400!-- Public interfaces
    405     PUBLIC  vm_check_parameters,                                               &
    406             vm_data_output,                                                    &
    407             vm_init,                                                           &
    408             vm_init_output,                                                    &
    409             vm_parin,                                                          &
     401    PUBLIC  vm_check_parameters,                                                                   &
     402            vm_data_output,                                                                        &
     403            vm_init,                                                                               &
     404            vm_init_output,                                                                        &
     405            vm_parin,                                                                              &
    410406            vm_sampling
    411407
    412408!
    413409!-- Public variables
    414     PUBLIC  dt_virtual_measurement,                                            &
    415             time_virtual_measurement,                                          &
    416             vmea,                                                              &
    417             vmea_general,                                                      &
     410    PUBLIC  dt_virtual_measurement,                                                                &
     411            time_virtual_measurement,                                                              &
     412            vmea,                                                                                  &
     413            vmea_general,                                                                          &
    418414            vm_time_start
    419415
     
    421417
    422418
    423 !------------------------------------------------------------------------------!
     419!--------------------------------------------------------------------------------------------------!
    424420! Description:
    425421! ------------
    426422!> Check parameters for virtual measurement module
    427 !------------------------------------------------------------------------------!
     423!--------------------------------------------------------------------------------------------------!
    428424 SUBROUTINE vm_check_parameters
    429425
     
    432428!-- Virtual measurements require a setup file.
    433429    IF ( .NOT. input_pids_vm )  THEN
    434        message_string = 'If virtual measurements are taken, a setup input ' // &
     430       message_string = 'If virtual measurements are taken, a setup input ' //                     &
    435431                        'file for the site locations is mandatory.'
    436432       CALL message( 'vm_check_parameters', 'PA0533', 1, 2, 0, 6, 0 )
     
    438434!
    439435!-- In case virtual measurements are taken, a static input file is required.
    440 !-- This is because UTM coordinates for the PALM domain origin are required
    441 !-- for correct mapping of the measurements.
     436!-- This is because UTM coordinates for the PALM domain origin are required for correct mapping of
     437!-- the measurements.
    442438!-- ToDo: Revise this later and remove this requirement.
    443439    IF ( .NOT. input_pids_static )  THEN
    444        message_string = 'If virtual measurements are taken, a static input ' //&
    445                         'file is mandatory.'
     440       message_string = 'If virtual measurements are taken, a static input file is mandatory.'
    446441       CALL message( 'vm_check_parameters', 'PA0534', 1, 2, 0, 6, 0 )
    447442    ENDIF
     
    451446!-- In case of non-parallel NetCDF the virtual measurement output is not
    452447!-- working. This is only designed for parallel NetCDF.
    453     message_string = 'If virtual measurements are taken, parallel ' //         &
    454                      'NetCDF is required.'
     448    message_string = 'If virtual measurements are taken, parallel NetCDF is required.'
    455449    CALL message( 'vm_check_parameters', 'PA0708', 1, 2, 0, 6, 0 )
    456450#endif
    457451!
    458 !-- Check if the given number of neighboring grid points do not exceeds the number
     452!-- Check if the given number of neighboring grid points do not exceed the number
    459453!-- of ghost points.
    460     IF ( off_pr > nbgp - 1  .OR.  off_ts > nbgp - 1  .OR.  off_tr > nbgp - 1 ) &
    461     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: ',     &
     454    IF ( off_pr > nbgp - 1  .OR.  off_ts > nbgp - 1  .OR.  off_tr > nbgp - 1 )  THEN
     455       WRITE(message_string,*)                                                                     &
     456                        'If virtual measurements are taken, the number ' //                        &
     457                        'of surrounding grid points must not be larger ' //                        &
     458                        'than the number of ghost points - 1, which is: ',                         &
    466459                        nbgp - 1
    467460       CALL message( 'vm_check_parameters', 'PA0705', 1, 2, 0, 6, 0 )
     
    475468 END SUBROUTINE vm_check_parameters
    476469
    477 !------------------------------------------------------------------------------!
     470!--------------------------------------------------------------------------------------------------!
    478471! Description:
    479472! ------------
    480 !> Subroutine defines variable attributes according to UC2 standard. Note, later
    481 !> this list can be moved to the data-output module where it can be re-used also
    482 !> for other output.
    483 !------------------------------------------------------------------------------!
    484   SUBROUTINE vm_set_attributes( output_variable )
    485 
    486      TYPE( virt_var_atts ), INTENT(INOUT) ::  output_variable !< data structure with attributes that need to be set
    487 
    488      output_variable%long_name     = 'none'
    489      output_variable%standard_name = 'none'
    490      output_variable%units         = 'none'
    491      output_variable%coordinates   = 'lon lat E_UTM N_UTM x y z time station_name'
    492      output_variable%grid_mapping  = 'crs'
    493 
    494      SELECT CASE ( TRIM( output_variable%name ) )
    495 
    496         CASE ( 'u' )
    497            output_variable%long_name     = 'u wind component'
    498            output_variable%units         = 'm s-1'
    499 
    500         CASE ( 'ua' )
    501            output_variable%long_name     = 'eastward wind'
    502            output_variable%standard_name = 'eastward_wind'
    503            output_variable%units         = 'm s-1'
    504 
    505         CASE ( 'v' )
    506            output_variable%long_name     = 'v wind component'
    507            output_variable%units         = 'm s-1'
    508 
    509         CASE ( 'va' )
    510            output_variable%long_name     = 'northward wind'
    511            output_variable%standard_name = 'northward_wind'
    512            output_variable%units         = 'm s-1'
    513 
    514         CASE ( 'w' )
    515            output_variable%long_name     = 'w wind component'
    516            output_variable%standard_name = 'upward_air_velocity'
    517            output_variable%units         = 'm s-1'
    518 
    519         CASE ( 'wspeed' )
    520            output_variable%long_name     = 'wind speed'
    521            output_variable%standard_name = 'wind_speed'
    522            output_variable%units         = 'm s-1'
    523 
    524         CASE ( 'wdir' )
    525            output_variable%long_name     = 'wind from direction'
    526            output_variable%standard_name = 'wind_from_direction'
    527            output_variable%units         = 'degrees'
    528 
    529         CASE ( 'theta' )
    530            output_variable%long_name     = 'air potential temperature'
    531            output_variable%standard_name = 'air_potential_temperature'
    532            output_variable%units         = 'K'
    533 
    534         CASE ( 'utheta' )
    535            output_variable%long_name     = 'eastward kinematic sensible heat flux in air'
    536            output_variable%units         = 'K m s-1'
    537 
    538         CASE ( 'vtheta' )
    539            output_variable%long_name     = 'northward kinematic sensible heat flux in air'
    540            output_variable%units         = 'K m s-1'
    541 
    542         CASE ( 'wtheta' )
    543            output_variable%long_name     = 'upward kinematic sensible heat flux in air'
    544            output_variable%units         = 'K m s-1'
    545 
    546         CASE ( 'ta' )
    547            output_variable%long_name     = 'air temperature'
    548            output_variable%standard_name = 'air_temperature'
    549            output_variable%units         = 'degree_C'
    550 
    551         CASE ( 'tva' )
    552            output_variable%long_name     = 'virtual acoustic temperature'
    553            output_variable%units         = 'K'
    554 
    555         CASE ( 'haa' )
    556            output_variable%long_name     = 'absolute atmospheric humidity'
    557            output_variable%units         = 'kg m-3'
    558 
    559         CASE ( 'hus' )
    560            output_variable%long_name     = 'specific humidity'
    561            output_variable%standard_name = 'specific_humidity'
    562            output_variable%units         = 'kg kg-1'
    563 
    564         CASE ( 'hur' )
    565            output_variable%long_name     = 'relative humidity'
    566            output_variable%standard_name = 'relative_humidity'
    567            output_variable%units         = '1'
    568 
    569         CASE ( 'rlu' )
    570            output_variable%long_name     = 'upwelling longwave flux in air'
    571            output_variable%standard_name = 'upwelling_longwave_flux_in_air'
    572            output_variable%units         = 'W m-2'
    573 
    574         CASE ( 'rlus' )
    575            output_variable%long_name     = 'surface upwelling longwave flux in air'
    576            output_variable%standard_name = 'surface_upwelling_longwave_flux_in_air'
    577            output_variable%units         = 'W m-2'
    578 
    579         CASE ( 'rld' )
    580            output_variable%long_name     = 'downwelling longwave flux in air'
    581            output_variable%standard_name = 'downwelling_longwave_flux_in_air'
    582            output_variable%units         = 'W m-2'
    583 
    584         CASE ( 'rsddif' )
    585            output_variable%long_name     = 'diffuse downwelling shortwave flux in air'
    586            output_variable%standard_name = 'diffuse_downwelling_shortwave_flux_in_air'
    587            output_variable%units         = 'W m-2'
    588 
    589         CASE ( 'rsd' )
    590            output_variable%long_name     = 'downwelling shortwave flux in air'
    591            output_variable%standard_name = 'downwelling_shortwave_flux_in_air'
    592            output_variable%units         = 'W m-2'
    593 
    594         CASE ( 'rnds' )
    595            output_variable%long_name     = 'surface net downward radiative flux'
    596            output_variable%standard_name = 'surface_net_downward_radiative_flux'
    597            output_variable%units         = 'W m-2'
    598 
    599         CASE ( 'rsu' )
    600            output_variable%long_name     = 'upwelling shortwave flux in air'
    601            output_variable%standard_name = 'upwelling_shortwave_flux_in_air'
    602            output_variable%units         = 'W m-2'
    603 
    604         CASE ( 'rsus' )
    605            output_variable%long_name     = 'surface upwelling shortwave flux in air'
    606            output_variable%standard_name = 'surface_upwelling_shortwave_flux_in_air'
    607            output_variable%units         = 'W m-2'
    608 
    609         CASE ( 'rsds' )
    610            output_variable%long_name     = 'surface downwelling shortwave flux in air'
    611            output_variable%standard_name = 'surface_downwelling_shortwave_flux_in_air'
    612            output_variable%units         = 'W m-2'
    613 
    614         CASE ( 'hfss' )
    615            output_variable%long_name     = 'surface upward sensible heat flux'
    616            output_variable%standard_name = 'surface_upward_sensible_heat_flux'
    617            output_variable%units         = 'W m-2'
    618 
    619         CASE ( 'hfls' )
    620            output_variable%long_name     = 'surface upward latent heat flux'
    621            output_variable%standard_name = 'surface_upward_latent_heat_flux'
    622            output_variable%units         = 'W m-2'
    623 
    624         CASE ( 'ts' )
    625            output_variable%long_name     = 'surface temperature'
    626            output_variable%standard_name = 'surface_temperature'
    627            output_variable%units         = 'K'
    628 
    629         CASE ( 'thetas' )
    630            output_variable%long_name     = 'surface layer temperature scale'
    631            output_variable%units         = 'K'
    632 
    633         CASE ( 'us' )
    634            output_variable%long_name     = 'friction velocity'
    635            output_variable%units         = 'm s-1'
    636 
    637         CASE ( 'uw' )
    638            output_variable%long_name     = 'upward eastward kinematic momentum flux in air'
    639            output_variable%units         = 'm2 s-2'
    640 
    641         CASE ( 'vw' )
    642            output_variable%long_name     = 'upward northward kinematic momentum flux in air'
    643            output_variable%units         = 'm2 s-2'
    644 
    645         CASE ( 'uv' )
    646            output_variable%long_name     = 'eastward northward kinematic momentum flux in air'
    647            output_variable%units         = 'm2 s-2'
    648 
    649         CASE ( 'plev' )
    650            output_variable%long_name     = 'air pressure'
    651            output_variable%standard_name = 'air_pressure'
    652            output_variable%units         = 'Pa'
    653 
    654         CASE ( 'm_soil' )
    655            output_variable%long_name     = 'soil moisture volumetric'
    656            output_variable%units         = 'm3 m-3'
    657 
    658         CASE ( 't_soil' )
    659            output_variable%long_name     = 'soil temperature'
    660            output_variable%standard_name = 'soil_temperature'
    661            output_variable%units         = 'degree_C'
    662 
    663         CASE ( 'hfdg' )
    664            output_variable%long_name     = 'downward heat flux at ground level in soil'
    665            output_variable%standard_name = 'downward_heat_flux_at_ground_level_in_soil'
    666            output_variable%units         = 'W m-2'
    667 
    668         CASE ( 'hfds' )
    669            output_variable%long_name     = 'downward heat flux in soil'
    670            output_variable%standard_name = 'downward_heat_flux_in_soil'
    671            output_variable%units         = 'W m-2'
    672 
    673         CASE ( 'hfla' )
    674            output_variable%long_name     = 'upward latent heat flux in air'
    675            output_variable%standard_name = 'upward_latent_heat_flux_in_air'
    676            output_variable%units         = 'W m-2'
    677 
    678         CASE ( 'hfsa' )
    679            output_variable%long_name     = 'upward latent heat flux in air'
    680            output_variable%standard_name = 'upward_sensible_heat_flux_in_air'
    681            output_variable%units         = 'W m-2'
    682 
    683         CASE ( 'jno2' )
    684            output_variable%long_name     = 'photolysis rate of nitrogen dioxide'
    685            output_variable%standard_name = 'photolysis_rate_of_nitrogen_dioxide'
    686            output_variable%units         = 's-1'
    687 
    688         CASE ( 'lwcs' )
    689            output_variable%long_name     = 'liquid water content of soil layer'
    690            output_variable%standard_name = 'liquid_water_content_of_soil_layer'
    691            output_variable%units         = 'kg m-2'
    692 
    693         CASE ( 'lwp' )
    694            output_variable%long_name     = 'liquid water path'
    695            output_variable%standard_name = 'atmosphere_mass_content_of_cloud_liquid_water'
    696            output_variable%units         = 'kg m-2'
    697 
    698         CASE ( 'ps' )
    699            output_variable%long_name     = 'surface air pressure'
    700            output_variable%standard_name = 'surface_air_pressure'
    701            output_variable%units         = 'hPa'
    702 
    703         CASE ( 'pswrtg' )
    704            output_variable%long_name     = 'platform speed wrt ground'
    705            output_variable%standard_name = 'platform_speed_wrt_ground'
    706            output_variable%units         = 'm s-1'
    707 
    708         CASE ( 'pswrta' )
    709            output_variable%long_name     = 'platform speed wrt air'
    710            output_variable%standard_name = 'platform_speed_wrt_air'
    711            output_variable%units         = 'm s-1'
    712 
    713         CASE ( 'pwv' )
    714            output_variable%long_name     = 'water vapor partial pressure in air'
    715            output_variable%standard_name = 'water_vapor_partial_pressure_in_air'
    716            output_variable%units         = 'hPa'
    717 
    718         CASE ( 'ssdu' )
    719            output_variable%long_name     = 'duration of sunshine'
    720            output_variable%standard_name = 'duration_of_sunshine'
    721            output_variable%units         = 's'
    722 
    723         CASE ( 't_lw' )
    724            output_variable%long_name     = 'land water temperature'
    725            output_variable%units         = 'degree_C'
    726 
    727         CASE ( 'tb' )
    728            output_variable%long_name     = 'brightness temperature'
    729            output_variable%standard_name = 'brightness_temperature'
    730            output_variable%units         = 'K'
    731 
    732         CASE ( 'uqv' )
    733            output_variable%long_name     = 'eastward kinematic latent heat flux in air'
    734            output_variable%units         = 'g kg-1 m s-1'
    735 
    736         CASE ( 'vqv' )
    737            output_variable%long_name     = 'northward kinematic latent heat flux in air'
    738            output_variable%units         = 'g kg-1 m s-1'
    739 
    740         CASE ( 'wqv' )
    741            output_variable%long_name     = 'upward kinematic latent heat flux in air'
    742            output_variable%units         = 'g kg-1 m s-1'
    743 
    744         CASE ( 'zcb' )
    745            output_variable%long_name     = 'cloud base altitude'
    746            output_variable%standard_name = 'cloud_base_altitude'
    747            output_variable%units         = 'm'
    748 
    749         CASE ( 'zmla' )
    750            output_variable%long_name     = 'atmosphere boundary layer thickness'
    751            output_variable%standard_name = 'atmosphere_boundary_layer_thickness'
    752            output_variable%units         = 'm'
    753 
    754         CASE ( 'mcpm1' )
    755            output_variable%long_name     = 'mass concentration of pm1 ambient aerosol particles in air'
    756            output_variable%standard_name = 'mass_concentration_of_pm1_ambient_aerosol_particles_in_air'
    757            output_variable%units         = 'kg m-3'
    758 
    759         CASE ( 'mcpm10' )
    760            output_variable%long_name     = 'mass concentration of pm10 ambient aerosol particles in air'
    761            output_variable%standard_name = 'mass_concentration_of_pm10_ambient_aerosol_particles_in_air'
    762            output_variable%units         = 'kg m-3'
    763 
    764         CASE ( 'mcpm2p5' )
    765            output_variable%long_name     = 'mass concentration of pm2p5 ambient aerosol particles in air'
    766            output_variable%standard_name = 'mass_concentration_of_pm2p5_ambient_aerosol_particles_in_air'
    767            output_variable%units         = 'kg m-3'
    768 
    769         CASE ( 'mfno', 'mcno'  )
    770            output_variable%long_name     = 'mole fraction of nitrogen monoxide in air'
    771            output_variable%standard_name = 'mole_fraction_of_nitrogen_monoxide_in_air'
    772            output_variable%units         = 'ppm' !'mol mol-1'
    773 
    774         CASE ( 'mfno2', 'mcno2'  )
    775            output_variable%long_name     = 'mole fraction of nitrogen dioxide in air'
    776            output_variable%standard_name = 'mole_fraction_of_nitrogen_dioxide_in_air'
    777            output_variable%units         = 'ppm' !'mol mol-1'
    778 
    779         CASE ( 'tro3'  )
    780            output_variable%long_name     = 'mole fraction of ozone in air'
    781            output_variable%standard_name = 'mole_fraction_of_ozone_in_air'
    782            output_variable%units         = 'ppm' !'mol mol-1'
    783 
    784         CASE DEFAULT
    785 
    786      END SELECT
    787 
    788   END SUBROUTINE vm_set_attributes
    789 
    790 
    791 !------------------------------------------------------------------------------!
     473!> Subroutine defines variable attributes according to UC2 standard. Note, later  this list can be
     474!> moved to the data-output module where it can be re-used also for other output.
     475!--------------------------------------------------------------------------------------------------!
     476 SUBROUTINE vm_set_attributes( output_variable )
     477
     478    TYPE( virt_var_atts ), INTENT(INOUT) ::  output_variable !< data structure with attributes that need to be set
     479
     480    output_variable%long_name     = 'none'
     481    output_variable%standard_name = 'none'
     482    output_variable%units         = 'none'
     483    output_variable%coordinates   = 'lon lat E_UTM N_UTM x y z time station_name'
     484    output_variable%grid_mapping  = 'crs'
     485
     486    SELECT CASE ( TRIM( output_variable%name ) )
     487
     488       CASE ( 'u' )
     489          output_variable%long_name     = 'u wind component'
     490          output_variable%units         = 'm s-1'
     491
     492       CASE ( 'ua' )
     493          output_variable%long_name     = 'eastward wind'
     494          output_variable%standard_name = 'eastward_wind'
     495          output_variable%units         = 'm s-1'
     496
     497       CASE ( 'v' )
     498          output_variable%long_name     = 'v wind component'
     499          output_variable%units         = 'm s-1'
     500
     501       CASE ( 'va' )
     502          output_variable%long_name     = 'northward wind'
     503          output_variable%standard_name = 'northward_wind'
     504          output_variable%units         = 'm s-1'
     505
     506       CASE ( 'w' )
     507          output_variable%long_name     = 'w wind component'
     508          output_variable%standard_name = 'upward_air_velocity'
     509          output_variable%units         = 'm s-1'
     510
     511       CASE ( 'wspeed' )
     512          output_variable%long_name     = 'wind speed'
     513          output_variable%standard_name = 'wind_speed'
     514          output_variable%units         = 'm s-1'
     515
     516       CASE ( 'wdir' )
     517          output_variable%long_name     = 'wind from direction'
     518          output_variable%standard_name = 'wind_from_direction'
     519          output_variable%units         = 'degrees'
     520
     521       CASE ( 'theta' )
     522          output_variable%long_name     = 'air potential temperature'
     523          output_variable%standard_name = 'air_potential_temperature'
     524          output_variable%units         = 'K'
     525
     526       CASE ( 'utheta' )
     527          output_variable%long_name     = 'eastward kinematic sensible heat flux in air'
     528          output_variable%units         = 'K m s-1'
     529
     530       CASE ( 'vtheta' )
     531          output_variable%long_name     = 'northward kinematic sensible heat flux in air'
     532          output_variable%units         = 'K m s-1'
     533
     534       CASE ( 'wtheta' )
     535          output_variable%long_name     = 'upward kinematic sensible heat flux in air'
     536          output_variable%units         = 'K m s-1'
     537
     538       CASE ( 'ta' )
     539          output_variable%long_name     = 'air temperature'
     540          output_variable%standard_name = 'air_temperature'
     541          output_variable%units         = 'degree_C'
     542
     543       CASE ( 'tva' )
     544          output_variable%long_name     = 'virtual acoustic temperature'
     545          output_variable%units         = 'K'
     546
     547       CASE ( 'haa' )
     548          output_variable%long_name     = 'absolute atmospheric humidity'
     549          output_variable%units         = 'kg m-3'
     550
     551       CASE ( 'hus' )
     552          output_variable%long_name     = 'specific humidity'
     553          output_variable%standard_name = 'specific_humidity'
     554          output_variable%units         = 'kg kg-1'
     555
     556       CASE ( 'hur' )
     557          output_variable%long_name     = 'relative humidity'
     558          output_variable%standard_name = 'relative_humidity'
     559          output_variable%units         = '1'
     560
     561       CASE ( 'rlu' )
     562          output_variable%long_name     = 'upwelling longwave flux in air'
     563          output_variable%standard_name = 'upwelling_longwave_flux_in_air'
     564          output_variable%units         = 'W m-2'
     565
     566       CASE ( 'rlus' )
     567          output_variable%long_name     = 'surface upwelling longwave flux in air'
     568          output_variable%standard_name = 'surface_upwelling_longwave_flux_in_air'
     569          output_variable%units         = 'W m-2'
     570
     571       CASE ( 'rld' )
     572          output_variable%long_name     = 'downwelling longwave flux in air'
     573          output_variable%standard_name = 'downwelling_longwave_flux_in_air'
     574          output_variable%units         = 'W m-2'
     575
     576       CASE ( 'rsddif' )
     577          output_variable%long_name     = 'diffuse downwelling shortwave flux in air'
     578          output_variable%standard_name = 'diffuse_downwelling_shortwave_flux_in_air'
     579          output_variable%units         = 'W m-2'
     580
     581       CASE ( 'rsd' )
     582          output_variable%long_name     = 'downwelling shortwave flux in air'
     583          output_variable%standard_name = 'downwelling_shortwave_flux_in_air'
     584          output_variable%units         = 'W m-2'
     585
     586       CASE ( 'rnds' )
     587          output_variable%long_name     = 'surface net downward radiative flux'
     588          output_variable%standard_name = 'surface_net_downward_radiative_flux'
     589          output_variable%units         = 'W m-2'
     590
     591       CASE ( 'rsu' )
     592          output_variable%long_name     = 'upwelling shortwave flux in air'
     593          output_variable%standard_name = 'upwelling_shortwave_flux_in_air'
     594          output_variable%units         = 'W m-2'
     595
     596       CASE ( 'rsus' )
     597          output_variable%long_name     = 'surface upwelling shortwave flux in air'
     598          output_variable%standard_name = 'surface_upwelling_shortwave_flux_in_air'
     599          output_variable%units         = 'W m-2'
     600
     601       CASE ( 'rsds' )
     602          output_variable%long_name     = 'surface downwelling shortwave flux in air'
     603          output_variable%standard_name = 'surface_downwelling_shortwave_flux_in_air'
     604          output_variable%units         = 'W m-2'
     605
     606       CASE ( 'hfss' )
     607          output_variable%long_name     = 'surface upward sensible heat flux'
     608          output_variable%standard_name = 'surface_upward_sensible_heat_flux'
     609          output_variable%units         = 'W m-2'
     610
     611       CASE ( 'hfls' )
     612          output_variable%long_name     = 'surface upward latent heat flux'
     613          output_variable%standard_name = 'surface_upward_latent_heat_flux'
     614          output_variable%units         = 'W m-2'
     615
     616       CASE ( 'ts' )
     617          output_variable%long_name     = 'surface temperature'
     618          output_variable%standard_name = 'surface_temperature'
     619          output_variable%units         = 'K'
     620
     621       CASE ( 'thetas' )
     622          output_variable%long_name     = 'surface layer temperature scale'
     623          output_variable%units         = 'K'
     624
     625       CASE ( 'us' )
     626          output_variable%long_name     = 'friction velocity'
     627          output_variable%units         = 'm s-1'
     628
     629       CASE ( 'uw' )
     630          output_variable%long_name     = 'upward eastward kinematic momentum flux in air'
     631          output_variable%units         = 'm2 s-2'
     632
     633       CASE ( 'vw' )
     634          output_variable%long_name     = 'upward northward kinematic momentum flux in air'
     635          output_variable%units         = 'm2 s-2'
     636
     637       CASE ( 'uv' )
     638          output_variable%long_name     = 'eastward northward kinematic momentum flux in air'
     639          output_variable%units         = 'm2 s-2'
     640
     641       CASE ( 'plev' )
     642          output_variable%long_name     = 'air pressure'
     643          output_variable%standard_name = 'air_pressure'
     644          output_variable%units         = 'Pa'
     645
     646       CASE ( 'm_soil' )
     647          output_variable%long_name     = 'soil moisture volumetric'
     648          output_variable%units         = 'm3 m-3'
     649
     650       CASE ( 't_soil' )
     651          output_variable%long_name     = 'soil temperature'
     652          output_variable%standard_name = 'soil_temperature'
     653          output_variable%units         = 'degree_C'
     654
     655       CASE ( 'hfdg' )
     656          output_variable%long_name     = 'downward heat flux at ground level in soil'
     657          output_variable%standard_name = 'downward_heat_flux_at_ground_level_in_soil'
     658          output_variable%units         = 'W m-2'
     659
     660       CASE ( 'hfds' )
     661          output_variable%long_name     = 'downward heat flux in soil'
     662          output_variable%standard_name = 'downward_heat_flux_in_soil'
     663          output_variable%units         = 'W m-2'
     664
     665       CASE ( 'hfla' )
     666          output_variable%long_name     = 'upward latent heat flux in air'
     667          output_variable%standard_name = 'upward_latent_heat_flux_in_air'
     668          output_variable%units         = 'W m-2'
     669
     670       CASE ( 'hfsa' )
     671          output_variable%long_name     = 'upward latent heat flux in air'
     672          output_variable%standard_name = 'upward_sensible_heat_flux_in_air'
     673          output_variable%units         = 'W m-2'
     674
     675       CASE ( 'jno2' )
     676          output_variable%long_name     = 'photolysis rate of nitrogen dioxide'
     677          output_variable%standard_name = 'photolysis_rate_of_nitrogen_dioxide'
     678          output_variable%units         = 's-1'
     679
     680       CASE ( 'lwcs' )
     681          output_variable%long_name     = 'liquid water content of soil layer'
     682          output_variable%standard_name = 'liquid_water_content_of_soil_layer'
     683          output_variable%units         = 'kg m-2'
     684
     685       CASE ( 'lwp' )
     686          output_variable%long_name     = 'liquid water path'
     687          output_variable%standard_name = 'atmosphere_mass_content_of_cloud_liquid_water'
     688          output_variable%units         = 'kg m-2'
     689
     690       CASE ( 'ps' )
     691          output_variable%long_name     = 'surface air pressure'
     692          output_variable%standard_name = 'surface_air_pressure'
     693          output_variable%units         = 'hPa'
     694
     695       CASE ( 'pswrtg' )
     696          output_variable%long_name     = 'platform speed wrt ground'
     697          output_variable%standard_name = 'platform_speed_wrt_ground'
     698          output_variable%units         = 'm s-1'
     699
     700       CASE ( 'pswrta' )
     701          output_variable%long_name     = 'platform speed wrt air'
     702          output_variable%standard_name = 'platform_speed_wrt_air'
     703          output_variable%units         = 'm s-1'
     704
     705       CASE ( 'pwv' )
     706          output_variable%long_name     = 'water vapor partial pressure in air'
     707          output_variable%standard_name = 'water_vapor_partial_pressure_in_air'
     708          output_variable%units         = 'hPa'
     709
     710       CASE ( 'ssdu' )
     711          output_variable%long_name     = 'duration of sunshine'
     712          output_variable%standard_name = 'duration_of_sunshine'
     713          output_variable%units         = 's'
     714
     715       CASE ( 't_lw' )
     716          output_variable%long_name     = 'land water temperature'
     717          output_variable%units         = 'degree_C'
     718
     719       CASE ( 'tb' )
     720          output_variable%long_name     = 'brightness temperature'
     721          output_variable%standard_name = 'brightness_temperature'
     722          output_variable%units         = 'K'
     723
     724       CASE ( 'uqv' )
     725          output_variable%long_name     = 'eastward kinematic latent heat flux in air'
     726          output_variable%units         = 'g kg-1 m s-1'
     727
     728       CASE ( 'vqv' )
     729          output_variable%long_name     = 'northward kinematic latent heat flux in air'
     730          output_variable%units         = 'g kg-1 m s-1'
     731
     732       CASE ( 'wqv' )
     733          output_variable%long_name     = 'upward kinematic latent heat flux in air'
     734          output_variable%units         = 'g kg-1 m s-1'
     735
     736       CASE ( 'zcb' )
     737          output_variable%long_name     = 'cloud base altitude'
     738          output_variable%standard_name = 'cloud_base_altitude'
     739          output_variable%units         = 'm'
     740
     741       CASE ( 'zmla' )
     742          output_variable%long_name     = 'atmosphere boundary layer thickness'
     743          output_variable%standard_name = 'atmosphere_boundary_layer_thickness'
     744          output_variable%units         = 'm'
     745
     746       CASE ( 'mcpm1' )
     747          output_variable%long_name     = 'mass concentration of pm1 ambient aerosol particles in air'
     748          output_variable%standard_name = 'mass_concentration_of_pm1_ambient_aerosol_particles_in_air'
     749          output_variable%units         = 'kg m-3'
     750
     751       CASE ( 'mcpm10' )
     752          output_variable%long_name     = 'mass concentration of pm10 ambient aerosol particles in air'
     753          output_variable%standard_name = 'mass_concentration_of_pm10_ambient_aerosol_particles_in_air'
     754          output_variable%units         = 'kg m-3'
     755
     756       CASE ( 'mcpm2p5' )
     757          output_variable%long_name     = 'mass concentration of pm2p5 ambient aerosol particles in air'
     758          output_variable%standard_name = 'mass_concentration_of_pm2p5_ambient_aerosol_particles_in_air'
     759          output_variable%units         = 'kg m-3'
     760
     761       CASE ( 'mfno', 'mcno'  )
     762          output_variable%long_name     = 'mole fraction of nitrogen monoxide in air'
     763          output_variable%standard_name = 'mole_fraction_of_nitrogen_monoxide_in_air'
     764          output_variable%units         = 'ppm' !'mol mol-1'
     765
     766       CASE ( 'mfno2', 'mcno2'  )
     767          output_variable%long_name     = 'mole fraction of nitrogen dioxide in air'
     768          output_variable%standard_name = 'mole_fraction_of_nitrogen_dioxide_in_air'
     769          output_variable%units         = 'ppm' !'mol mol-1'
     770
     771       CASE ( 'tro3'  )
     772          output_variable%long_name     = 'mole fraction of ozone in air'
     773          output_variable%standard_name = 'mole_fraction_of_ozone_in_air'
     774          output_variable%units         = 'ppm' !'mol mol-1'
     775
     776       CASE DEFAULT
     777
     778    END SELECT
     779
     780 END SUBROUTINE vm_set_attributes
     781
     782
     783!--------------------------------------------------------------------------------------------------!
    792784! Description:
    793785! ------------
    794786!> Read namelist for the virtual measurement module
    795 !------------------------------------------------------------------------------!
     787!--------------------------------------------------------------------------------------------------!
    796788 SUBROUTINE vm_parin
    797789
    798     CHARACTER (LEN=80) ::  line   !< dummy string that contains the current line of the parameter file
    799 
    800     NAMELIST /virtual_measurement_parameters/  dt_virtual_measurement,         &
    801                                                off_ts,                         &
    802                                                off_pr,                         &
    803                                                off_tr,                         &
    804                                                use_virtual_measurement,        &
     790    CHARACTER(LEN=80) ::  line   !< dummy string that contains the current line of the parameter file
     791
     792    NAMELIST /virtual_measurement_parameters/  dt_virtual_measurement,                             &
     793                                               off_ts,                                             &
     794                                               off_pr,                                             &
     795                                               off_tr,                                             &
     796                                               use_virtual_measurement,                            &
    805797                                               vm_time_start
    806798
     
    810802    REWIND ( 11 )
    811803    line = ' '
    812     DO WHILE ( INDEX( line, '&virtual_measurement_parameters' ) == 0 )
     804    DO  WHILE ( INDEX( line, '&virtual_measurement_parameters' ) == 0 )
    813805       READ ( 11, '(A)', END=20 )  line
    814806    ENDDO
     
    822814!-- Set flag that indicates that the virtual measurement module is switched on
    823815    IF ( use_virtual_measurement )  virtual_measurement = .TRUE.
    824 
    825816    GOTO 20
    826817
     
    834825
    835826
    836 !------------------------------------------------------------------------------!
     827!--------------------------------------------------------------------------------------------------!
    837828! Description:
    838829! ------------
    839 !> Initialize virtual measurements: read coordiante arrays and measured
    840 !> variables, set indicies indicating the measurement points, read further
    841 !> attributes, etc..
    842 !------------------------------------------------------------------------------!
     830!> Initialize virtual measurements: read coordiante arrays and measured variables, set indicies
     831!> indicating the measurement points, read further attributes, etc..
     832!--------------------------------------------------------------------------------------------------!
    843833 SUBROUTINE vm_init
    844834
    845     CHARACTER(LEN=5)                  ::  dum                          !< dummy string indicating station id
    846     CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables_file = '' !< array with all measured variables read from NetCDF
    847     CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables      = '' !< dummy array with all measured variables that are allowed
    848 
    849     INTEGER(iwp) ::  dim_ntime !< dimension size of time coordinate
    850     INTEGER(iwp) ::  i         !< grid index of virtual observation point in x-direction
    851     INTEGER(iwp) ::  is        !< grid index of real observation point of the respective station in x-direction
    852     INTEGER(iwp) ::  j         !< grid index of observation point in x-direction
    853     INTEGER(iwp) ::  js        !< grid index of real observation point of the respective station in y-direction
    854     INTEGER(iwp) ::  k         !< grid index of observation point in x-direction
    855     INTEGER(iwp) ::  kl        !< lower vertical index of surrounding grid points of an observation coordinate
    856     INTEGER(iwp) ::  ks        !< grid index of real observation point of the respective station in z-direction
    857     INTEGER(iwp) ::  ksurf     !< topography top index
    858     INTEGER(iwp) ::  ku        !< upper vertical index of surrounding grid points of an observation coordinate
    859     INTEGER(iwp) ::  l         !< running index over all stations
    860     INTEGER(iwp) ::  len_char  !< character length of single measured variables without Null character
    861     INTEGER(iwp) ::  ll        !< running index over all measured variables in file
    862     INTEGER(iwp) ::  m         !< running index for surface elements
    863     INTEGER(iwp) ::  n         !< running index over trajectory coordinates
    864     INTEGER(iwp) ::  nofill    !< dummy for nofill return value (not used)
    865     INTEGER(iwp) ::  ns        !< counter variable for number of observation points on subdomain
    866     INTEGER(iwp) ::  off       !< number of surrounding grid points to be sampled
    867     INTEGER(iwp) ::  t         !< running index over number of trajectories
    868 
    869     INTEGER(KIND=1)                             ::  soil_dum !< dummy variable to input a soil flag
    870 
    871     INTEGER(iwp), DIMENSION(:), ALLOCATABLE     ::  ns_all !< dummy array used to sum-up the number of observation coordinates
     835    CHARACTER(LEN=5)                  ::  dum                           !< dummy string indicating station id
     836    CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables_file = ''  !< array with all measured variables read from NetCDF
     837    CHARACTER(LEN=100), DIMENSION(50) ::  measured_variables      = ''  !< dummy array with all measured variables that are allowed
     838
     839    INTEGER(iwp) ::  dim_ntime  !< dimension size of time coordinate
     840    INTEGER(iwp) ::  i          !< grid index of virtual observation point in x-direction
     841    INTEGER(iwp) ::  is         !< grid index of real observation point of the respective station in x-direction
     842    INTEGER(iwp) ::  j          !< grid index of observation point in x-direction
     843    INTEGER(iwp) ::  js         !< grid index of real observation point of the respective station in y-direction
     844    INTEGER(iwp) ::  k          !< grid index of observation point in x-direction
     845    INTEGER(iwp) ::  kl         !< lower vertical index of surrounding grid points of an observation coordinate
     846    INTEGER(iwp) ::  ks         !< grid index of real observation point of the respective station in z-direction
     847    INTEGER(iwp) ::  ksurf      !< topography top index
     848    INTEGER(iwp) ::  ku         !< upper vertical index of surrounding grid points of an observation coordinate
     849    INTEGER(iwp) ::  l          !< running index over all stations
     850    INTEGER(iwp) ::  len_char   !< character length of single measured variables without Null character
     851    INTEGER(iwp) ::  ll         !< running index over all measured variables in file
     852    INTEGER(iwp) ::  m          !< running index for surface elements
     853    INTEGER(iwp) ::  n          !< running index over trajectory coordinates
     854    INTEGER(iwp) ::  nofill     !< dummy for nofill return value (not used)
     855    INTEGER(iwp) ::  ns         !< counter variable for number of observation points on subdomain
     856    INTEGER(iwp) ::  off        !< number of surrounding grid points to be sampled
     857    INTEGER(iwp) ::  t          !< running index over number of trajectories
     858
     859    INTEGER(KIND=1)                             ::  soil_dum  !< dummy variable to input a soil flag
     860
     861    INTEGER(iwp), DIMENSION(:), ALLOCATABLE     ::  ns_all  !< dummy array used to sum-up the number of observation coordinates
    872862
    873863#if defined( __parallel )
    874     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  ns_atmos !< number of observation points for each station on each mpi rank
    875     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  ns_soil  !< number of observation points for each station on each mpi rank
     864    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  ns_atmos  !< number of observation points for each station on each mpi rank
     865    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE   ::  ns_soil   !< number of observation points for each station on each mpi rank
    876866#endif
    877867
    878     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  meas_flag !< mask array indicating measurement positions
    879 
    880     LOGICAL  ::  on_pe        !< flag indicating that the respective measurement coordinate is on subdomain
     868    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  meas_flag  !< mask array indicating measurement positions
     869
     870    LOGICAL  ::  on_pe  !< flag indicating that the respective measurement coordinate is on subdomain
    881871
    882872    REAL(wp) ::  fill_eutm !< _FillValue for coordinate array E_UTM
     
    884874    REAL(wp) ::  fill_zar  !< _FillValue for height coordinate
    885875
    886     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm     !< easting UTM coordinate, temporary variable
    887     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm     !< northing UTM coordinate, temporary variable
    888     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm_tmp !< EUTM coordinate before rotation
    889     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm_tmp !< NUTM coordinate before rotation
    890     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  station_h !< station height above reference
    891     REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zar       !< observation height above reference
     876    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm      !< easting UTM coordinate, temporary variable
     877    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  e_utm_tmp  !< EUTM coordinate before rotation
     878    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm      !< northing UTM coordinate, temporary variable
     879    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  n_utm_tmp  !< NUTM coordinate before rotation
     880    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  station_h  !< station height above reference
     881    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zar        !< observation height above reference
    892882#if defined( __netcdf )
    893883!
     
    896886!
    897887!-- Obtain number of sites.
    898     CALL get_attribute( pids_id,                                               &
    899                         char_numstations,                                      &
    900                         vmea_general%nvm,                                      &
    901                         global_attribute )
    902 !
    903 !-- Allocate data structure which encompass all required information, such as
    904 !-- grid points indicies, absolute UTM coordinates, the measured quantities,
    905 !-- etc. .
     888    CALL get_attribute( pids_id, char_numstations, vmea_general%nvm, global_attribute )
     889!
     890!-- Allocate data structure which encompasses all required information, such as  grid points indicies,
     891!-- absolute UTM coordinates, the measured quantities, etc. .
    906892    ALLOCATE( vmea(1:vmea_general%nvm) )
    907893!
    908 !-- Allocate flag array. This dummy array is used to identify grid points
    909 !-- where virtual measurements should be taken. Please note, in order to
    910 !-- include also the surrounding grid points of the original coordinate
    911 !-- ghost points are required.
     894!-- Allocate flag array. This dummy array is used to identify grid points where virtual measurements
     895!-- should be taken. Please note, in order to include also the surrounding grid points of the
     896!-- original coordinate, ghost points are required.
    912897    ALLOCATE( meas_flag(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    913898    meas_flag = 0
     
    916901    DO  l = 1, vmea_general%nvm
    917902!
    918 !--    Determine suffix which contains the ID, ordered according to the number
    919 !--    of measurements.
     903!--    Determine suffix which contains the ID, ordered according to the number of measurements.
    920904       IF( l < 10 )  THEN
    921905          WRITE( dum, '(I1)')  l
     
    931915!
    932916!--    Read the origin site coordinates (UTM).
    933        CALL get_attribute( pids_id,                                            &
    934                            char_origx // TRIM( dum ),                          &
    935                            vmea(l)%origin_x_obs,                               &
    936                            global_attribute )
    937        CALL get_attribute( pids_id,                                            &
    938                            char_origy // TRIM( dum ),                          &
    939                            vmea(l)%origin_y_obs,                               &
    940                            global_attribute )
     917       CALL get_attribute( pids_id, char_origx // TRIM( dum ), vmea(l)%origin_x_obs, global_attribute )
     918       CALL get_attribute( pids_id, char_origy // TRIM( dum ), vmea(l)%origin_y_obs, global_attribute )
    941919!
    942920!--    Read site name.
    943        CALL get_attribute( pids_id,                                            &
    944                            char_site // TRIM( dum ),                           &
    945                            vmea(l)%site,                                       &
    946                            global_attribute )
    947 !
    948 !--    Read a flag which indicates that also soil quantities are take at the
    949 !--    respective site (is part of the virtual measurement driver).
    950        CALL get_attribute( pids_id,                                            &
    951                            char_soil // TRIM( dum ),                           &
    952                            soil_dum,                                           &
    953                            global_attribute )
     921       CALL get_attribute( pids_id, char_site // TRIM( dum ), vmea(l)%site, global_attribute )
     922!
     923!--    Read a flag which indicates that also soil quantities are take at the respective site
     924!--    (is part of the virtual measurement driver).
     925       CALL get_attribute( pids_id, char_soil // TRIM( dum ), soil_dum, global_attribute )
    954926!
    955927!--    Set flag indicating soil-sampling.
     
    957929!
    958930!--    Read type of the measurement (trajectory, profile, timeseries).
    959        CALL get_attribute( pids_id,                                            &
    960                            char_feature // TRIM( dum ),                        &
    961                            vmea(l)%feature_type,                               &
    962                            global_attribute )
     931       CALL get_attribute( pids_id, char_feature // TRIM( dum ), vmea(l)%feature_type, global_attribute )
    963932!
    964933!---   Set logicals depending on the type of the measurement
     
    972941!--    Give error message in case the type matches non of the pre-defined types.
    973942       ELSE
    974           message_string = 'Attribue featureType = ' //                        &
    975                            TRIM( vmea(l)%feature_type ) //                     &
    976                            ' is not allowed.'
     943          message_string = 'Attribue featureType = ' // TRIM( vmea(l)%feature_type ) // ' is not allowed.'
    977944          CALL message( 'vm_init', 'PA0535', 1, 2, 0, 6, 0 )
    978945       ENDIF
     
    980947!--    Read string with all measured variables at this site.
    981948       measured_variables_file = ''
    982        CALL get_variable( pids_id,                                             &
    983                           char_mv // TRIM( dum ),                              &
    984                           measured_variables_file )
     949       CALL get_variable( pids_id, char_mv // TRIM( dum ), measured_variables_file )
    985950!
    986951!--    Count the number of measured variables.
    987 !--    Please note, for some NetCDF interal reasons characters end with a NULL,
    988 !--    i.e. also empty characters contain a NULL. Therefore, check the strings
    989 !--    for a NULL to get the correct character length in order to compare
    990 !--    them with the list of allowed variables.
     952!--    Please note, for some NetCDF interal reasons, characters end with a NULL, i.e. also empty
     953!--    characters contain a NULL. Therefore, check the strings for a NULL to get the correct
     954!--    character length in order to compare them with the list of allowed variables.
    991955       vmea(l)%nmeas  = 1
    992        DO ll = 1, SIZE( measured_variables_file )
    993           IF ( measured_variables_file(ll)(1:1) /= CHAR(0)  .AND.              &
     956       DO  ll = 1, SIZE( measured_variables_file )
     957          IF ( measured_variables_file(ll)(1:1) /= CHAR(0)  .AND.                                  &
    994958               measured_variables_file(ll)(1:1) /= ' ')  THEN
    995959!
    996960!--          Obtain character length of the character
    997961             len_char = 1
    998              DO WHILE ( measured_variables_file(ll)(len_char:len_char) /= CHAR(0)&
    999                  .AND.  measured_variables_file(ll)(len_char:len_char) /= ' ' )
     962             DO  WHILE ( measured_variables_file(ll)(len_char:len_char) /= CHAR(0)  .AND.          &
     963                 measured_variables_file(ll)(len_char:len_char) /= ' ' )
    1000964                len_char = len_char + 1
    1001965             ENDDO
    1002966             len_char = len_char - 1
    1003967
    1004              measured_variables(vmea(l)%nmeas) =                               &
    1005                                        measured_variables_file(ll)(1:len_char)
     968             measured_variables(vmea(l)%nmeas) = measured_variables_file(ll)(1:len_char)
    1006969             vmea(l)%nmeas = vmea(l)%nmeas + 1
    1007970
     
    1010973       vmea(l)%nmeas = vmea(l)%nmeas - 1
    1011974!
    1012 !--    Allocate data-type array for the measured variables names and attributes
    1013 !--    at the respective site.
     975!--    Allocate data-type array for the measured variables names and attributes at the respective
     976!--    site.
    1014977       ALLOCATE( vmea(l)%var_atts(1:vmea(l)%nmeas) )
    1015978!
    1016 !--    Store the variable names in a data structures, which assigns further
    1017 !--    attributes to this name. Further, for data output reasons, create a
    1018 !--    string of output variables, which will be written into the attribute
    1019 !--    data_content.
     979!--    Store the variable names in a data structure, which assigns further attributes to this name.
     980!--    Further, for data output reasons, create a string of output variables, which will be written
     981!--    into the attribute data_content.
    1020982       DO  ll = 1, vmea(l)%nmeas
    1021983          vmea(l)%var_atts(ll)%name = TRIM( measured_variables(ll) )
    1022984
    1023           vmea(l)%data_content = TRIM( vmea(l)%data_content ) // " " //        &
     985          vmea(l)%data_content = TRIM( vmea(l)%data_content ) // " " //                            &
    1024986                                 TRIM( vmea(l)%var_atts(ll)%name )
    1025987       ENDDO
    1026988!
    1027 !--    Read all the UTM coordinates for the site. Based on the coordinates,
    1028 !--    define the grid-index space on each subdomain where virtual measurements
    1029 !--    should be taken. Note, the entire coordinate array (on the entire model
    1030 !--    domain) won't be stored as this would exceed memory requirements,
    1031 !--    particularly for trajectories.
     989!--    Read all the UTM coordinates for the site. Based on the coordinates, define the grid-index
     990!--    space on each subdomain where virtual measurements should be taken. Note, the entire
     991!--    coordinate array (on the entire model domain) won't be stored as this would exceed memory
     992!--    requirements, particularly for trajectories.
    1032993       IF ( vmea(l)%nmeas > 0 )  THEN
    1033994!
    1034 !--       For stationary measurements UTM coordinates are just one value and
    1035 !--       its dimension is "station", while for mobile measurements UTM
    1036 !--       coordinates are arrays depending on the number of trajectories and
    1037 !--       time, according to (UC)2 standard. First, inquire dimension length
    1038 !--       of the UTM coordinates.
     995!--       For stationary measurements UTM coordinates are just one value and its dimension is
     996!--       "station", while for mobile measurements UTM coordinates are arrays depending on the
     997!--       number of trajectories and time, according to (UC)2 standard. First, inquire dimension
     998!--       length of the UTM coordinates.
    1039999          IF ( vmea(l)%trajectory )  THEN
    10401000!
    1041 !--          For non-stationary measurements read the number of trajectories
    1042 !--          and the number of time coordinates.
    1043              CALL get_dimension_length( pids_id,                               &
    1044                                         vmea(l)%n_tr_st,                       &
    1045                                         "traj" // TRIM( dum ) )
    1046              CALL get_dimension_length( pids_id,                               &
    1047                                         dim_ntime,                             &
    1048                                         "ntime" // TRIM( dum ) )
    1049 !
    1050 !--       For stationary measurements the dimension for UTM is station
    1051 !--       and for the time-coordinate it is one.
     1001!--          For non-stationary measurements read the number of trajectories and the number of time
     1002!--          coordinates.
     1003             CALL get_dimension_length( pids_id, vmea(l)%n_tr_st, "traj" // TRIM( dum ) )
     1004             CALL get_dimension_length( pids_id, dim_ntime, "ntime" // TRIM( dum ) )
     1005!
     1006!--       For stationary measurements the dimension for UTM is station and for the time-coordinate
     1007!--       it is one.
    10521008          ELSE
    1053              CALL get_dimension_length( pids_id,                               &
    1054                                         vmea(l)%n_tr_st,                       &
    1055                                         "station" // TRIM( dum ) )
     1009             CALL get_dimension_length( pids_id, vmea(l)%n_tr_st, "station" // TRIM( dum ) )
    10561010             dim_ntime = 1
    10571011          ENDIF
    10581012!
    1059 !-        Allocate array which defines individual time/space frame for each
    1060 !--       trajectory or station.
     1013!-        Allocate array which defines individual time/space frame for each trajectory or station.
    10611014          ALLOCATE( vmea(l)%dim_t(1:vmea(l)%n_tr_st) )
    10621015!
    1063 !--       Allocate temporary arrays for UTM and height coordinates. Note,
    1064 !--       on file UTM coordinates might be 1D or 2D variables
     1016!--       Allocate temporary arrays for UTM and height coordinates. Note, on file UTM coordinates
     1017!--       might be 1D or 2D variables
    10651018          ALLOCATE( e_utm(1:vmea(l)%n_tr_st,1:dim_ntime)       )
    10661019          ALLOCATE( n_utm(1:vmea(l)%n_tr_st,1:dim_ntime)       )
     
    10751028          ALLOCATE( n_utm_tmp(1:vmea(l)%n_tr_st,1:dim_ntime) )
    10761029!
    1077 !--       Read UTM and height coordinates coordinates for all trajectories and
    1078 !--       times. Note, in case these obtain any missing values, replace them
    1079 !--       with default _FillValues.
    1080           CALL inquire_fill_value( pids_id,                                    &
    1081                                    char_eutm // TRIM( dum ),                   &
    1082                                    nofill,                                     &
    1083                                    fill_eutm )
    1084           CALL inquire_fill_value( pids_id,                                    &
    1085                                    char_nutm // TRIM( dum ),                   &
    1086                                    nofill,                                     &
    1087                                    fill_nutm )
    1088           CALL inquire_fill_value( pids_id,                                    &
    1089                                    char_zar // TRIM( dum ),                    &
    1090                                    nofill,                                     &
    1091                                    fill_zar )
    1092 !
    1093 !--       Further line is just to avoid compiler warnings. nofill might be used
    1094 !--       in future.
     1030!--       Read UTM and height coordinates for all trajectories and times. Note, in case
     1031!--       these obtain any missing values, replace them with default _FillValues.
     1032          CALL inquire_fill_value( pids_id, char_eutm // TRIM( dum ), nofill, fill_eutm )
     1033          CALL inquire_fill_value( pids_id, char_nutm // TRIM( dum ), nofill, fill_nutm )
     1034          CALL inquire_fill_value( pids_id, char_zar // TRIM( dum ), nofill, fill_zar )
     1035!
     1036!--       Further line is just to avoid compiler warnings. nofill might be used in future.
    10951037          IF ( nofill == 0  .OR.  nofill /= 0 )  CONTINUE
    10961038!
    1097 !--       Read observation coordinates. Please note, for trajectories the
    1098 !--       observation height is stored directly in z, while for timeSeries
    1099 !--       it is stored in z - station_h, according to UC2-standard.
     1039!--       Read observation coordinates. Please note, for trajectories the observation height is
     1040!--       stored directly in z, while for timeSeries it is stored in z - station_h, according to
     1041!--       UC2-standard.
    11001042          IF ( vmea(l)%trajectory )  THEN
    1101              CALL get_variable( pids_id,                                       &
    1102                                 char_eutm // TRIM( dum ),                      &
    1103                                 e_utm,                                         &
    1104                                 0, dim_ntime-1,                                &
    1105                                 0, vmea(l)%n_tr_st-1 )
    1106              CALL get_variable( pids_id,                                       &
    1107                                 char_nutm // TRIM( dum ),                      &
    1108                                 n_utm,                                         &
    1109                                 0, dim_ntime-1,                                &
    1110                                 0, vmea(l)%n_tr_st-1 )
    1111              CALL get_variable( pids_id,                                       &
    1112                                 char_zar // TRIM( dum ),                       &
    1113                                 zar,                                           &
    1114                                 0, dim_ntime-1,                                &
    1115                                 0, vmea(l)%n_tr_st-1 )
     1043             CALL get_variable( pids_id, char_eutm // TRIM( dum ), e_utm, 0, dim_ntime-1, 0,       &
     1044                                vmea(l)%n_tr_st-1 )
     1045             CALL get_variable( pids_id, char_nutm // TRIM( dum ), n_utm, 0, dim_ntime-1, 0,       &
     1046                                vmea(l)%n_tr_st-1 )
     1047             CALL get_variable( pids_id, char_zar // TRIM( dum ), zar, 0, dim_ntime-1, 0,          &
     1048                                vmea(l)%n_tr_st-1 )
    11161049          ELSE
    1117              CALL get_variable( pids_id,                                       &
    1118                                 char_eutm // TRIM( dum ),                      &
    1119                                 e_utm(:,1) )
    1120              CALL get_variable( pids_id,                                       &
    1121                                 char_nutm // TRIM( dum ),                      &
    1122                                 n_utm(:,1) )
    1123              CALL get_variable( pids_id,                                       &
    1124                                 char_station_h // TRIM( dum ),                 &
    1125                                 station_h(:,1) )
    1126              CALL get_variable( pids_id,                                       &
    1127                                 char_zar // TRIM( dum ),                       &
    1128                                 zar(:,1) )
     1050             CALL get_variable( pids_id, char_eutm // TRIM( dum ), e_utm(:,1) )
     1051             CALL get_variable( pids_id, char_nutm // TRIM( dum ), n_utm(:,1) )
     1052             CALL get_variable( pids_id, char_station_h // TRIM( dum ), station_h(:,1) )
     1053             CALL get_variable( pids_id, char_zar // TRIM( dum ), zar(:,1) )
    11291054          ENDIF
    11301055
     
    11361061          zar  = zar - station_h
    11371062!
    1138 !--       Based on UTM coordinates, check if the measurement station or parts
    1139 !--       of the trajectory are on subdomain. This case, setup grid index space
    1140 !--       sample these quantities.
     1063!--       Based on UTM coordinates, check if the measurement station or parts of the trajectory are
     1064!--       on subdomain. This case, setup grid index space sample these quantities.
    11411065          meas_flag = 0
    11421066          DO  t = 1, vmea(l)%n_tr_st
    11431067!
    1144 !--          First, compute relative x- and y-coordinates with respect to the
    1145 !--          lower-left origin of the model domain, which is the difference
    1146 !--          between UTM coordinates. Note, if the origin is not correct, the
    1147 !--          virtual sites will be misplaced. Further, in case of an rotated
    1148 !--          model domain, the UTM coordinates must be also rotated.
     1068!--          First, compute relative x- and y-coordinates with respect to the lower-left origin of
     1069!--          the model domain, which is the difference between UTM coordinates. Note, if the origin
     1070!--          is not correct, the virtual sites will be misplaced. Further, in case of an rotated
     1071!--          model domain, the UTM coordinates must also be rotated.
    11491072             e_utm_tmp(t,1:dim_ntime) = e_utm(t,1:dim_ntime) - init_model%origin_x
    11501073             n_utm_tmp(t,1:dim_ntime) = n_utm(t,1:dim_ntime) - init_model%origin_y
    1151              e_utm(t,1:dim_ntime) = COS( init_model%rotation_angle * pi / 180.0_wp ) &
    1152                                     * e_utm_tmp(t,1:dim_ntime)                       &
    1153                                   - SIN( init_model%rotation_angle * pi / 180.0_wp ) &
     1074             e_utm(t,1:dim_ntime) = COS( init_model%rotation_angle * pi / 180.0_wp )               &
     1075                                    * e_utm_tmp(t,1:dim_ntime)                                     &
     1076                                  - SIN( init_model%rotation_angle * pi / 180.0_wp )               &
    11541077                                    * n_utm_tmp(t,1:dim_ntime)
    1155              n_utm(t,1:dim_ntime) = SIN( init_model%rotation_angle * pi / 180.0_wp ) &
    1156                                     * e_utm_tmp(t,1:dim_ntime)                       &
    1157                                   + COS( init_model%rotation_angle * pi / 180.0_wp ) &
     1078             n_utm(t,1:dim_ntime) = SIN( init_model%rotation_angle * pi / 180.0_wp )               &
     1079                                    * e_utm_tmp(t,1:dim_ntime)                                     &
     1080                                  + COS( init_model%rotation_angle * pi / 180.0_wp )               &
    11581081                                    * n_utm_tmp(t,1:dim_ntime)
    11591082!
    1160 !--          Determine the individual time coordinate length for each station and
    1161 !--          trajectory. This is required as several stations and trajectories
    1162 !--          are merged into one file but they do not have the same number of
    1163 !--          points in time, hence, missing values may occur and cannot be
    1164 !--          processed further. This is actually a work-around for the specific
    1165 !--          (UC)2 dataset, but it won't harm anyway.
     1083!--          Determine the individual time coordinate length for each station and trajectory. This
     1084!--          is required as several stations and trajectories are merged into one file but they do
     1085!--          not have the same number of points in time, hence, missing values may occur and cannot
     1086!--          be processed further. This is actually a work-around for the specific (UC)2 dataset,
     1087!--          but it won't harm anyway.
    11661088             vmea(l)%dim_t(t) = 0
    11671089             DO  n = 1, dim_ntime
    1168                 IF ( e_utm(t,n) /= fill_eutm  .AND.                            &
    1169                      n_utm(t,n) /= fill_nutm  .AND.                            &
     1090                IF ( e_utm(t,n) /= fill_eutm  .AND.  n_utm(t,n) /= fill_nutm  .AND.                &
    11701091                     zar(t,n)   /= fill_zar )  vmea(l)%dim_t(t) = n
    11711092             ENDDO
    11721093!
    1173 !--          Compute grid indices relative to origin and check if these are
    1174 !--          on the subdomain. Note, virtual measurements will be taken also
    1175 !--          at grid points surrounding the station, hence, check also for
    1176 !--          these grid points.
    1177 !--          The number of surrounding grid points is set according to the
    1178 !--          featureType.
     1094!--          Compute grid indices relative to origin and check if these are on the subdomain. Note,
     1095!--          virtual measurements will be taken also at grid points surrounding the station, hence,
     1096!--          check also for these grid points. The number of surrounding grid points is set
     1097!--          according to the featureType.
    11791098             IF ( vmea(l)%timseries_profile )  THEN
    11801099                off = off_pr
     
    11861105
    11871106             DO  n = 1, vmea(l)%dim_t(t)
    1188                 is = INT( ( e_utm(t,n) + 0.5_wp * dx ) * ddx, KIND = iwp )
    1189                 js = INT( ( n_utm(t,n) + 0.5_wp * dy ) * ddy, KIND = iwp )
     1107                 is = INT( ( e_utm(t,n) + 0.5_wp * dx ) * ddx, KIND = iwp )
     1108                 js = INT( ( n_utm(t,n) + 0.5_wp * dy ) * ddy, KIND = iwp )
    11901109!
    11911110!--             Is the observation point on subdomain?
    1192                 on_pe = ( is >= nxl  .AND.  is <= nxr  .AND.                   &
    1193                           js >= nys  .AND.  js <= nyn )
    1194 !
    1195 !--             Check if observation coordinate is on subdomain
     1111                on_pe = ( is >= nxl  .AND.  is <= nxr  .AND.  js >= nys  .AND.  js <= nyn )
     1112!
     1113!--             Check if observation coordinate is on subdomain.
    11961114                IF ( on_pe )  THEN
    11971115!
    1198 !--                Determine vertical index which correspond to the observation
    1199 !--                height.
     1116!--                Determine vertical index which corresponds to the observation height.
    12001117                   ksurf = topo_top_ind(js,is,0)
    12011118                   ks = MINLOC( ABS( zu - zw(ksurf) - zar(t,n) ), DIM = 1 ) - 1
    12021119!
    1203 !--                Set mask array at the observation coordinates. Also, flag the
    1204 !--                surrounding coordinate points, but first check whether the
    1205 !--                surrounding coordinate points are on the subdomain.
     1120!--                Set mask array at the observation coordinates. Also, flag the surrounding
     1121!--                coordinate points, but first check whether the surrounding coordinate points are
     1122!--                on the subdomain.
    12061123                   kl = MERGE( ks-off, ksurf, ks-off >= nzb  .AND. ks-off >= ksurf )
    12071124                   ku = MERGE( ks+off, nzt,   ks+off < nzt+1 )
     
    12101127                      DO  j = js-off, js+off
    12111128                         DO  k = kl, ku
    1212                             meas_flag(k,j,i) = MERGE(                           &
    1213                                           IBSET( meas_flag(k,j,i), 0 ),         &
    1214                                           0,                                    &
    1215                                           BTEST( wall_flags_total_0(k,j,i), 0 ) &
    1216                                                     )
     1129                            meas_flag(k,j,i) = MERGE( IBSET( meas_flag(k,j,i), 0 ), 0,             &
     1130                                               BTEST( wall_flags_total_0(k,j,i), 0 ) )
    12171131                         ENDDO
    12181132                      ENDDO
     
    12231137          ENDDO
    12241138!
    1225 !--       Based on the flag array count the number of sampling coordinates.
    1226 !--       Please note, sampling coordinates in atmosphere and soil may be
    1227 !--       different, as within the soil all levels will be measured.
    1228 !--       Hence, count individually. Start with atmoshere.
     1139!--       Based on the flag array, count the number of sampling coordinates. Please note, sampling
     1140!--       coordinates in atmosphere and soil may be different, as within the soil all levels will be
     1141!--       measured. Hence, count individually. Start with atmoshere.
    12291142          ns = 0
    12301143          DO  i = nxl-off, nxr+off
     
    12371150
    12381151!
    1239 !--       Store number of observation points on subdomain and allocate index
    1240 !--       arrays as well as array containing height information.
     1152!--       Store number of observation points on subdomain and allocate index arrays as well as array
     1153!--       containing height information.
    12411154          vmea(l)%ns = ns
    12421155
     
    12461159          ALLOCATE( vmea(l)%zar(1:vmea(l)%ns) )
    12471160!
    1248 !--       Based on the flag array store the grid indices which correspond to
    1249 !--       the observation coordinates.
     1161!--       Based on the flag array store the grid indices which correspond to the observation
     1162!--       coordinates.
    12501163          ns = 0
    12511164          DO  i = nxl-off, nxr+off
     
    12631176          ENDDO
    12641177!
    1265 !--       Same for the soil. Based on the flag array, count the number of
    1266 !--       sampling coordinates in soil. Sample at all soil levels in this case.
    1267 !--       Please note, soil variables can only be sampled on subdomains, not
    1268 !--       on ghost layers.
     1178!--       Same for the soil. Based on the flag array, count the number of sampling coordinates in
     1179!--       soil. Sample at all soil levels in this case. Please note, soil variables can only be
     1180!--       sampled on subdomains, not on ghost layers.
    12691181          IF ( vmea(l)%soil_sampling )  THEN
    12701182             DO  i = nxl, nxr
    12711183                DO  j = nys, nyn
    12721184                   IF ( ANY( BTEST( meas_flag(:,j,i), 0 ) ) )  THEN
    1273                       IF ( surf_lsm_h%start_index(j,i) <=                      &
    1274                            surf_lsm_h%end_index(j,i) )  THEN
    1275                          vmea(l)%ns_soil = vmea(l)%ns_soil +                   &
    1276                                                       nzt_soil - nzb_soil + 1
     1185                      IF ( surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i) )  THEN
     1186                         vmea(l)%ns_soil = vmea(l)%ns_soil + nzt_soil - nzb_soil + 1
    12771187                      ENDIF
    1278                       IF ( surf_usm_h%start_index(j,i) <=                      &
    1279                            surf_usm_h%end_index(j,i) )  THEN
    1280                          vmea(l)%ns_soil = vmea(l)%ns_soil +                   &
    1281                                                       nzt_wall - nzb_wall + 1
     1188                      IF ( surf_usm_h%start_index(j,i) <= surf_usm_h%end_index(j,i) )  THEN
     1189                         vmea(l)%ns_soil = vmea(l)%ns_soil + nzt_wall - nzb_wall + 1
    12821190                      ENDIF
    12831191                   ENDIF
     
    12861194          ENDIF
    12871195!
    1288 !--       Allocate index arrays as well as array containing height information
    1289 !--       for soil.
     1196!--       Allocate index arrays as well as array containing height information for soil.
    12901197          IF ( vmea(l)%soil_sampling )  THEN
    12911198             ALLOCATE( vmea(l)%i_soil(1:vmea(l)%ns_soil) )
     
    13011208                DO  j = nys, nyn
    13021209                   IF ( ANY( BTEST( meas_flag(:,j,i), 0 ) ) )  THEN
    1303                       IF ( surf_lsm_h%start_index(j,i) <=                      &
    1304                            surf_lsm_h%end_index(j,i) )  THEN
     1210                      IF ( surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i) )  THEN
    13051211                         m = surf_lsm_h%start_index(j,i)
    13061212                         DO  k = nzb_soil, nzt_soil
     
    13131219                      ENDIF
    13141220
    1315                       IF ( surf_usm_h%start_index(j,i) <=                      &
    1316                            surf_usm_h%end_index(j,i) )  THEN
     1221                      IF ( surf_usm_h%start_index(j,i) <= surf_usm_h%end_index(j,i) )  THEN
    13171222                         m = surf_usm_h%start_index(j,i)
    13181223                         DO  k = nzb_wall, nzt_wall
     
    13321237          ALLOCATE( vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nmeas) )
    13331238
    1334           IF ( vmea(l)%soil_sampling )                                         &
    1335              ALLOCATE( vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil,           &
    1336                                                   1:vmea(l)%nmeas) )
     1239          IF ( vmea(l)%soil_sampling )                                                             &
     1240             ALLOCATE( vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil, 1:vmea(l)%nmeas) )
    13371241!
    13381242!--       Initialize with _FillValues
    13391243          vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nmeas) = vmea(l)%fillout
    1340           IF ( vmea(l)%soil_sampling )                                         &
    1341              vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil,1:vmea(l)%nmeas) =   &
    1342                                                                 vmea(l)%fillout
     1244          IF ( vmea(l)%soil_sampling )                                                             &
     1245             vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil,1:vmea(l)%nmeas) = vmea(l)%fillout
    13431246!
    13441247!--       Deallocate temporary coordinate arrays
     
    13661269    ns_all = 0
    13671270#if defined( __parallel )
    1368     CALL MPI_ALLREDUCE( vmea(:)%ns, ns_all(:), vmea_general%nvm, MPI_INTEGER,  &
    1369                         MPI_SUM, comm2d, ierr )
     1271    CALL MPI_ALLREDUCE( vmea(:)%ns, ns_all(:), vmea_general%nvm,                                   &
     1272                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
    13701273#else
    13711274    ns_all(:) = vmea(:)%ns
     
    13761279    ns_all = 0
    13771280#if defined( __parallel )
    1378     CALL MPI_ALLREDUCE( vmea(:)%ns_soil, ns_all(:), vmea_general%nvm,          &
     1281    CALL MPI_ALLREDUCE( vmea(:)%ns_soil, ns_all(:), vmea_general%nvm,                              &
    13791282                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
    13801283#else
     
    13851288    DEALLOCATE( ns_all )
    13861289!
    1387 !-- In case of parallel NetCDF the start coordinate for each mpi rank needs to
    1388 !-- be defined, so that each processor knows where to write the data.
     1290!-- In case of parallel NetCDF the start coordinate for each mpi rank needs to be defined, so that
     1291!-- each processor knows where to write the data.
    13891292#if defined( __netcdf4_parallel )
    13901293    ALLOCATE( ns_atmos(0:numprocs-1,1:vmea_general%nvm) )
     
    13991302
    14001303#if defined( __parallel )
    1401     CALL MPI_ALLREDUCE( MPI_IN_PLACE, ns_atmos, numprocs * vmea_general%nvm,   &
     1304    CALL MPI_ALLREDUCE( MPI_IN_PLACE, ns_atmos, numprocs * vmea_general%nvm,                       &
    14021305                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
    1403     CALL MPI_ALLREDUCE( MPI_IN_PLACE, ns_soil, numprocs * vmea_general%nvm,    &
     1306    CALL MPI_ALLREDUCE( MPI_IN_PLACE, ns_soil, numprocs * vmea_general%nvm,                        &
    14041307                        MPI_INTEGER, MPI_SUM, comm2d, ierr )
    14051308#else
     
    14091312
    14101313!
    1411 !-- Determine the start coordinate in NetCDF file for the local arrays.
    1412 !-- Note, start coordinates are initialized with zero for sake of simplicity
    1413 !-- in summation. However, in NetCDF the start coordinates must be >= 1,
    1414 !-- so that a one needs to be added at the end.
     1314!-- Determine the start coordinate in NetCDF file for the local arrays. Note, start coordinates are
     1315!-- initialized with zero for sake of simplicity in summation. However, in NetCDF the start
     1316!-- coordinates must be >= 1, so that a one needs to be added at the end.
    14151317    DO  l = 1, vmea_general%nvm
    14161318       DO  n  = 0, myid - 1
     
    14351337#endif
    14361338
    1437   END SUBROUTINE vm_init
    1438 
    1439 
    1440 !------------------------------------------------------------------------------!
     1339 END SUBROUTINE vm_init
     1340
     1341
     1342!--------------------------------------------------------------------------------------------------!
    14411343! Description:
    14421344! ------------
    14431345!> Initialize output using data-output module
    1444 !------------------------------------------------------------------------------!
     1346!--------------------------------------------------------------------------------------------------!
    14451347 SUBROUTINE vm_init_output
    14461348
    14471349    CHARACTER(LEN=100) ::  variable_name  !< name of output variable
    14481350
    1449     INTEGER(iwp) ::  l              !< loop index
    1450     INTEGER(iwp) ::  n              !< loop index
    1451     INTEGER      ::  return_value   !< returned status value of called function
     1351    INTEGER(iwp) ::  l             !< loop index
     1352    INTEGER(iwp) ::  n             !< loop index
     1353    INTEGER      ::  return_value  !< returned status value of called function
    14521354
    14531355    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  ndim !< dummy to write dimension
    14541356
    1455     REAL(wp) ::  dum_lat !< transformed geographical coordinate (latitude)
    1456     REAL(wp) ::  dum_lon !< transformed geographical coordinate (longitude)
     1357    REAL(wp) ::  dum_lat  !< transformed geographical coordinate (latitude)
     1358    REAL(wp) ::  dum_lon  !< transformed geographical coordinate (longitude)
    14571359
    14581360!
    14591361!-- Determine the number of output timesteps.
    1460     ntimesteps = CEILING(                                                      &
    1461                   ( end_time - MAX( vm_time_start, time_since_reference_point )&
     1362    ntimesteps = CEILING(                                                                          &
     1363                  ( end_time - MAX( vm_time_start, time_since_reference_point )                    &
    14621364                  ) / dt_virtual_measurement )
    14631365!
     
    14721374!
    14731375!--    Define output file.
    1474        WRITE( vmea(l)%nc_filename, '(A,I4.4)' ) 'VM_OUTPUT' //                 &
    1475                                                 TRIM( coupling_char ) // '/' //&
    1476                                                 'site', l
     1376       WRITE( vmea(l)%nc_filename, '(A,I4.4)' ) 'VM_OUTPUT' // TRIM( coupling_char ) // '/' //     &
     1377              'site', l
    14771378
    14781379       return_value = dom_def_file( vmea(l)%nc_filename, 'netcdf4-parallel' )
     
    14801381!--    Define global attributes.
    14811382!--    Before, transform UTM into geographical coordinates.
    1482        CALL convert_utm_to_geographic( crs_list,                               &
    1483                                        vmea(l)%origin_x_obs,                   &
    1484                                        vmea(l)%origin_y_obs,                   &
    1485                                        dum_lon,                                &
    1486                                        dum_lat )
    1487 
    1488        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1489                                    attribute_name = 'site',                    &
     1383       CALL convert_utm_to_geographic( crs_list, vmea(l)%origin_x_obs, vmea(l)%origin_y_obs,       &
     1384                                       dum_lon, dum_lat )
     1385
     1386       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1387                                   attribute_name = 'site',                                        &
    14901388                                   value = TRIM( vmea(l)%site ) )
    1491        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1492                                    attribute_name = 'title',                   &
     1389       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1390                                   attribute_name = 'title',                                       &
    14931391                                   value = 'Virtual measurement output')
    1494        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1495                                    attribute_name = 'source',                  &
     1392       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1393                                   attribute_name = 'source',                                      &
    14961394                                   value = 'PALM-4U')
    1497        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1498                                    attribute_name = 'institution',             &
     1395       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1396                                   attribute_name = 'institution',                                 &
    14991397                                   value = input_file_atts%institution )
    1500        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1501                                    attribute_name = 'acronym',                 &
     1398       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1399                                   attribute_name = 'acronym',                                     &
    15021400                                   value = input_file_atts%acronym )
    1503        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1504                                    attribute_name = 'author',                  &
     1401       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1402                                   attribute_name = 'author',                                      &
    15051403                                   value = input_file_atts%author )
    1506        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1507                                    attribute_name = 'contact_person',          &
     1404       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1405                                   attribute_name = 'contact_person',                              &
    15081406                                   value = input_file_atts%contact_person )
    1509        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1510                                    attribute_name = 'iop',                     &
     1407       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1408                                   attribute_name = 'iop',                                         &
    15111409                                   value = input_file_atts%campaign )
    1512        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1513                                    attribute_name = 'campaign',                &
     1410       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1411                                   attribute_name = 'campaign',                                    &
    15141412                                   value = 'PALM-4U' )
    1515        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1516                                    attribute_name = 'origin_time ',            &
     1413       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1414                                   attribute_name = 'origin_time ',                                &
    15171415                                   value = origin_date_time)
    1518        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1519                                    attribute_name = 'location',                &
     1416       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1417                                   attribute_name = 'location',                                    &
    15201418                                   value = input_file_atts%location )
    1521        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1522                                    attribute_name = 'origin_x',                &
     1419       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1420                                   attribute_name = 'origin_x',                                    &
    15231421                                   value = vmea(l)%origin_x_obs )
    1524        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1525                                    attribute_name = 'origin_y',                &
     1422       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1423                                   attribute_name = 'origin_y',                                    &
    15261424                                   value = vmea(l)%origin_y_obs )
    1527        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1528                                    attribute_name = 'origin_lon',              &
     1425       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1426                                   attribute_name = 'origin_lon',                                  &
    15291427                                   value = dum_lon )
    1530        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1531                                    attribute_name = 'origin_lat',              &
     1428       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1429                                   attribute_name = 'origin_lat',                                  &
    15321430                                   value = dum_lat )
    1533        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1534                                    attribute_name = 'origin_z',                &
     1431       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1432                                   attribute_name = 'origin_z',                                    &
    15351433                                   value = 0.0 )
    1536        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1537                                    attribute_name = 'rotation_angle',          &
     1434       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1435                                   attribute_name = 'rotation_angle',                              &
    15381436                                   value = input_file_atts%rotation_angle )
    1539        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1540                                    attribute_name = 'featureType',             &
     1437       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1438                                   attribute_name = 'featureType',                                 &
    15411439                                   value = TRIM( vmea(l)%feature_type_out ) )
    1542        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1543                                    attribute_name = 'data_content',            &
     1440       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1441                                   attribute_name = 'data_content',                                &
    15441442                                   value = TRIM( vmea(l)%data_content ) )
    1545        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1546                                    attribute_name = 'creation_time',           &
     1443       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1444                                   attribute_name = 'creation_time',                               &
    15471445                                   value = input_file_atts%creation_time )
    1548        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1549                                    attribute_name = 'version',                 &
     1446       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1447                                   attribute_name = 'version',                                     &
    15501448                                   value = 1 ) !input_file_atts%version )
    1551        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1552                                    attribute_name = 'creation_time',           &
     1449       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1450                                   attribute_name = 'creation_time',                               &
    15531451                                   value = TRIM( vmea(l)%site ) )
    1554        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1555                                    attribute_name = 'Conventions',             &
     1452       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1453                                   attribute_name = 'Conventions',                                 &
    15561454                                   value = input_file_atts%conventions )
    1557        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1558                                    attribute_name = 'dependencies',            &
     1455       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1456                                   attribute_name = 'dependencies',                                &
    15591457                                   value = input_file_atts%dependencies )
    1560        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1561                                    attribute_name = 'history',                 &
     1458       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1459                                   attribute_name = 'history',                                     &
    15621460                                   value = input_file_atts%history )
    1563        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1564                                    attribute_name = 'references',              &
     1461       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1462                                   attribute_name = 'references',                                  &
    15651463                                   value = input_file_atts%references )
    1566        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1567                                    attribute_name = 'comment',                 &
     1464       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1465                                   attribute_name = 'comment',                                     &
    15681466                                   value = input_file_atts%comment )
    1569        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1570                                    attribute_name = 'keywords',                &
     1467       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1468                                   attribute_name = 'keywords',                                    &
    15711469                                   value = input_file_atts%keywords )
    1572        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1573                                    attribute_name = 'licence',                 &
    1574                                    value = '[UC]2 Open Licence; see [UC]2 ' // &
    1575                                            'data policy available at ' //      &
     1470       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1471                                   attribute_name = 'licence',                                     &
     1472                                   value = '[UC]2 Open Licence; see [UC]2 ' //                     &
     1473                                           'data policy available at ' //                          &
    15761474                                           'www.uc2-program.org/uc2_data_policy.pdf' )
    15771475!
     
    15821480          ndim(n) = n
    15831481       ENDDO
    1584        return_value = dom_def_dim( vmea(l)%nc_filename,                        &
    1585                                    dimension_name = 'station',                 &
    1586                                    output_type = 'int32',                      &
    1587                                    bounds = (/1_iwp, vmea(l)%ns_tot/),         &
     1482       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'station',                &
     1483                                   output_type = 'int32', bounds = (/1_iwp, vmea(l)%ns_tot/),      &
    15881484                                   values_int32 = ndim )
    15891485       DEALLOCATE( ndim )
     
    15951491       ENDDO
    15961492
    1597        return_value = dom_def_dim( vmea(l)%nc_filename,                        &
    1598                                    dimension_name = 'ntime',                   &
    1599                                    output_type = 'int32',                      &
    1600                                    bounds = (/1_iwp, ntimesteps/),             &
     1493       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'ntime',                  &
     1494                                   output_type = 'int32', bounds = (/1_iwp, ntimesteps/),          &
    16011495                                   values_int32 = ndim )
    16021496       DEALLOCATE( ndim )
     
    16081502       ENDDO
    16091503
    1610        return_value = dom_def_dim( vmea(l)%nc_filename,                        &
    1611                                    dimension_name = 'nv',                      &
    1612                                    output_type = 'int32',                      &
    1613                                    bounds = (/1_iwp, 2_iwp/),                  &
     1504       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'nv',                     &
     1505                                   output_type = 'int32', bounds = (/1_iwp, 2_iwp/),               &
    16141506                                   values_int32 = ndim )
    16151507       DEALLOCATE( ndim )
     
    16211513       ENDDO
    16221514
    1623        return_value = dom_def_dim( vmea(l)%nc_filename,                        &
    1624                                    dimension_name = 'max_name_len',            &
    1625                                    output_type = 'int32',                      &
    1626                                    bounds = (/1_iwp, maximum_name_length /),   &
    1627                                    values_int32 = ndim )
     1515       return_value = dom_def_dim( vmea(l)%nc_filename, dimension_name = 'max_name_len',           &
     1516                                   output_type = 'int32',                                          &
     1517                                   bounds = (/1_iwp, maximum_name_length /), values_int32 = ndim )
    16281518       DEALLOCATE( ndim )
    16291519!
     
    16311521!--    time
    16321522       variable_name = 'time'
    1633        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1634                                    variable_name = variable_name,              &
    1635                                    dimension_names = (/ 'station  ',           &
    1636                                                         'ntime    '/),         &
     1523       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1524                                   dimension_names = (/ 'station  ', 'ntime    '/),                &
    16371525                                   output_type = 'real32' )
    16381526!
    16391527!--    station_name
    16401528       variable_name = 'station_name'
    1641        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1642                                    variable_name = variable_name,              &
    1643                                    dimension_names = (/ 'max_name_len',        &
    1644                                                         'station     ' /),     &
     1529       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1530                                   dimension_names = (/ 'max_name_len', 'station     ' /),         &
    16451531                                   output_type = 'char' )
    16461532!
    16471533!--    vrs (vertical reference system)
    16481534       variable_name = 'vrs'
    1649        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1650                                    variable_name = variable_name,              &
    1651                                    dimension_names = (/ 'station' /),          &
    1652                                    output_type = 'int8' )
     1535       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1536                                   dimension_names = (/ 'station' /), output_type = 'int8' )
    16531537!
    16541538!--    crs (coordinate reference system)
    16551539       variable_name = 'crs'
    1656        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1657                                    variable_name = variable_name,              &
    1658                                    dimension_names = (/ 'station' /),          &
    1659                                    output_type = 'int8' )
     1540       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1541                                   dimension_names = (/ 'station' /), output_type = 'int8' )
    16601542!
    16611543!--    z
    16621544       variable_name = 'z'
    1663        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1664                                    variable_name = variable_name,              &
    1665                                    dimension_names = (/'station'/),            &
    1666                                    output_type = 'real32' )
     1545       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1546                                   dimension_names = (/'station'/), output_type = 'real32' )
    16671547!
    16681548!--    station_h
    16691549       variable_name = 'station_h'
    1670        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1671                                    variable_name = variable_name,              &
    1672                                    dimension_names = (/'station'/),            &
    1673                                    output_type = 'real32' )
     1550       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1551                                   dimension_names = (/'station'/), output_type = 'real32' )
    16741552!
    16751553!--    x
    16761554       variable_name = 'x'
    1677        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1678                                    variable_name = variable_name,              &
    1679                                    dimension_names = (/'station'/),            &
    1680                                    output_type = 'real32' )
     1555       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1556                                   dimension_names = (/'station'/), output_type = 'real32' )
    16811557!
    16821558!--    y
    16831559       variable_name = 'y'
    1684        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1685                                    variable_name = variable_name,              &
    1686                                    dimension_names = (/'station'/),            &
    1687                                    output_type = 'real32' )
     1560       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1561                                   dimension_names = (/'station'/), output_type = 'real32' )
    16881562!
    16891563!--    E-UTM
    16901564       variable_name = 'E_UTM'
    1691        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1692                                    variable_name = variable_name,              &
    1693                                    dimension_names = (/'station'/),            &
    1694                                    output_type = 'real32' )
     1565       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1566                                   dimension_names = (/'station'/), output_type = 'real32' )
    16951567!
    16961568!--    N-UTM
    16971569       variable_name = 'N_UTM'
    1698        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1699                                    variable_name = variable_name,              &
    1700                                    dimension_names = (/'station'/),            &
    1701                                    output_type = 'real32' )
     1570       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1571                                   dimension_names = (/'station'/), output_type = 'real32' )
    17021572!
    17031573!--    latitude
    17041574       variable_name = 'lat'
    1705        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1706                                    variable_name = variable_name,              &
    1707                                    dimension_names = (/'station'/),            &
    1708                                    output_type = 'real32' )
     1575       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1576                                   dimension_names = (/'station'/), output_type = 'real32' )
    17091577!
    17101578!--    longitude
    17111579       variable_name = 'lon'
    1712        return_value = dom_def_var( vmea(l)%nc_filename,                        &
    1713                                    variable_name = variable_name,              &
    1714                                    dimension_names = (/'station'/),            &
    1715                                    output_type = 'real32' )
    1716 !
    1717 !--    Set attributes for the coordinate variables. Note, not all coordinates
    1718 !--    have the same number of attributes.
     1580       return_value = dom_def_var( vmea(l)%nc_filename, variable_name = variable_name,             &
     1581                                   dimension_names = (/'station'/), output_type = 'real32' )
     1582!
     1583!--    Set attributes for the coordinate variables. Note, not all coordinates have the same number
     1584!--    of attributes.
    17191585!--    Units
    1720        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1721                                    variable_name = 'time',                     &
    1722                                    attribute_name = char_unit,                 &
     1586       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1587                                   variable_name = 'time',                                         &
     1588                                   attribute_name = char_unit,                                     &
    17231589                                   value = 'seconds since ' // origin_date_time )
    1724        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1725                                    variable_name = 'z',                        &
    1726                                    attribute_name = char_unit,                 &
     1590       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1591                                   variable_name = 'z',                                            &
     1592                                   attribute_name = char_unit,                                     &
    17271593                                   value = 'm' )
    1728        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1729                                    variable_name = 'station_h',                &
    1730                                    attribute_name = char_unit,                 &
     1594       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1595                                   variable_name = 'station_h',                                    &
     1596                                   attribute_name = char_unit,                                     &
    17311597                                   value = 'm' )
    1732        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1733                                    variable_name = 'x',                        &
    1734                                    attribute_name = char_unit,                 &
     1598       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1599                                   variable_name = 'x',                                            &
     1600                                   attribute_name = char_unit,                                     &
    17351601                                   value = 'm' )
    1736        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1737                                    variable_name = 'y',                        &
    1738                                    attribute_name = char_unit,                 &
     1602       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1603                                   variable_name = 'y',                                            &
     1604                                   attribute_name = char_unit,                                     &
    17391605                                   value = 'm' )
    1740        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1741                                    variable_name = 'E_UTM',                    &
    1742                                    attribute_name = char_unit,                 &
     1606       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1607                                   variable_name = 'E_UTM',                                        &
     1608                                   attribute_name = char_unit,                                     &
    17431609                                   value = 'm' )
    1744        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1745                                    variable_name = 'N_UTM',                    &
    1746                                    attribute_name = char_unit,                 &
     1610       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1611                                   variable_name = 'N_UTM',                                        &
     1612                                   attribute_name = char_unit,                                     &
    17471613                                   value = 'm' )
    1748        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1749                                    variable_name = 'lat',                      &
    1750                                    attribute_name = char_unit,                 &
     1614       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1615                                   variable_name = 'lat',                                          &
     1616                                   attribute_name = char_unit,                                     &
    17511617                                   value = 'degrees_north' )
    1752        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1753                                    variable_name = 'lon',                      &
    1754                                    attribute_name = char_unit,                 &
     1618       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1619                                   variable_name = 'lon',                                          &
     1620                                   attribute_name = char_unit,                                     &
    17551621                                   value = 'degrees_east' )
    17561622!
    17571623!--    Long name
    1758        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1759                                    variable_name = 'station_name',             &
    1760                                    attribute_name = char_long,                 &
     1624       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1625                                   variable_name = 'station_name',                                 &
     1626                                   attribute_name = char_long,                                     &
    17611627                                   value = 'station name')
    1762        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1763                                    variable_name = 'time',                     &
    1764                                    attribute_name = char_long,                 &
     1628       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1629                                   variable_name = 'time',                                         &
     1630                                   attribute_name = char_long,                                     &
    17651631                                   value = 'time')
    1766        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1767                                    variable_name = 'z',                        &
    1768                                    attribute_name = char_long,                 &
     1632       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1633                                   variable_name = 'z',                                            &
     1634                                   attribute_name = char_long,                                     &
    17691635                                   value = 'height above origin' )
    1770        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1771                                    variable_name = 'station_h',                &
    1772                                    attribute_name = char_long,                 &
     1636       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1637                                   variable_name = 'station_h',                                    &
     1638                                   attribute_name = char_long,                                     &
    17731639                                   value = 'surface altitude' )
    1774        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1775                                    variable_name = 'x',                        &
    1776                                    attribute_name = char_long,                 &
    1777                                    value = 'distance to origin in x-direction' )
    1778        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1779                                    variable_name = 'y',                        &
    1780                                    attribute_name = char_long,                 &
    1781                                    value = 'distance to origin in y-direction' )
    1782        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1783                                    variable_name = 'E_UTM',                    &
    1784                                    attribute_name = char_long,                 &
     1640       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1641                                   variable_name = 'x',                                            &
     1642                                   attribute_name = char_long,                                     &
     1643                                   value = 'distance to origin in x-direction')
     1644       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1645                                   variable_name = 'y',                                            &
     1646                                   attribute_name = char_long,                                     &
     1647                                   value = 'distance to origin in y-direction')
     1648       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1649                                   variable_name = 'E_UTM',                                        &
     1650                                   attribute_name = char_long,                                     &
    17851651                                   value = 'easting' )
    1786        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1787                                    variable_name = 'N_UTM',                    &
    1788                                    attribute_name = char_long,                 &
     1652       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1653                                   variable_name = 'N_UTM',                                        &
     1654                                   attribute_name = char_long,                                     &
    17891655                                   value = 'northing' )
    1790        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1791                                    variable_name = 'lat',                      &
    1792                                    attribute_name = char_long,                 &
     1656       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1657                                   variable_name = 'lat',                                          &
     1658                                   attribute_name = char_long,                                     &
    17931659                                   value = 'latitude' )
    1794        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1795                                    variable_name = 'lon',                      &
    1796                                    attribute_name = char_long,                 &
     1660       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1661                                   variable_name = 'lon',                                          &
     1662                                   attribute_name = char_long,                                     &
    17971663                                   value = 'longitude' )
    17981664!
    17991665!--    Standard name
    1800        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1801                                    variable_name = 'station_name',             &
    1802                                    attribute_name = char_standard,             &
     1666       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1667                                   variable_name = 'station_name',                                 &
     1668                                   attribute_name = char_standard,                                 &
    18031669                                   value = 'platform_name')
    1804        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1805                                    variable_name = 'time',                     &
    1806                                    attribute_name = char_standard,             &
     1670       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1671                                   variable_name = 'time',                                         &
     1672                                   attribute_name = char_standard,                                 &
    18071673                                   value = 'time')
    1808        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1809                                    variable_name = 'z',                        &
    1810                                    attribute_name = char_standard,             &
     1674       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1675                                   variable_name = 'z',                                            &
     1676                                   attribute_name = char_standard,                                 &
    18111677                                   value = 'height_above_mean_sea_level' )
    1812        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1813                                    variable_name = 'station_h',                &
    1814                                    attribute_name = char_standard,             &
     1678       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1679                                   variable_name = 'station_h',                                    &
     1680                                   attribute_name = char_standard,                                 &
    18151681                                   value = 'surface_altitude' )
    1816        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1817                                    variable_name = 'E_UTM',                    &
    1818                                    attribute_name = char_standard,             &
     1682       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1683                                   variable_name = 'E_UTM',                                        &
     1684                                   attribute_name = char_standard,                                 &
    18191685                                   value = 'projection_x_coordinate' )
    1820        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1821                                    variable_name = 'N_UTM',                    &
    1822                                    attribute_name = char_standard,             &
     1686       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1687                                   variable_name = 'N_UTM',                                        &
     1688                                   attribute_name = char_standard,                                 &
    18231689                                   value = 'projection_y_coordinate' )
    1824        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1825                                    variable_name = 'lat',                      &
    1826                                    attribute_name = char_standard,             &
     1690       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1691                                   variable_name = 'lat',                                          &
     1692                                   attribute_name = char_standard,                                 &
    18271693                                   value = 'latitude' )
    1828        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1829                                    variable_name = 'lon',                      &
    1830                                    attribute_name = char_standard,             &
     1694       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1695                                   variable_name = 'lon',                                          &
     1696                                   attribute_name = char_standard,                                 &
    18311697                                   value = 'longitude' )
    18321698!
    18331699!--    Axis
    1834        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1835                                    variable_name = 'time',                     &
    1836                                    attribute_name = 'axis',                    &
     1700       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1701                                   variable_name = 'time',                                         &
     1702                                   attribute_name = 'axis',                                        &
    18371703                                   value = 'T')
    1838        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1839                                    variable_name = 'z',                        &
    1840                                    attribute_name = 'axis',                    &
     1704       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1705                                   variable_name = 'z',                                            &
     1706                                   attribute_name = 'axis',                                        &
    18411707                                   value = 'Z' )
    1842        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1843                                    variable_name = 'x',                        &
    1844                                    attribute_name = 'axis',                    &
     1708       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1709                                   variable_name = 'x',                                            &
     1710                                   attribute_name = 'axis',                                        &
    18451711                                   value = 'X' )
    1846        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1847                                    variable_name = 'y',                        &
    1848                                    attribute_name = 'axis',                    &
     1712       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1713                                   variable_name = 'y',                                            &
     1714                                   attribute_name = 'axis',                                        &
    18491715                                   value = 'Y' )
    18501716!
    18511717!--    Set further individual attributes for the coordinate variables.
    18521718!--    For station name
    1853        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1854                                    variable_name = 'station_name',             &
    1855                                    attribute_name = 'cf_role',                 &
     1719       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1720                                   variable_name = 'station_name',                                 &
     1721                                   attribute_name = 'cf_role',                                     &
    18561722                                   value = 'timeseries_id' )
    18571723!
    18581724!--    For time
    1859        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1860                                    variable_name = 'time',                     &
    1861                                    attribute_name = 'calendar',                &
     1725       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1726                                   variable_name = 'time',                                         &
     1727                                   attribute_name = 'calendar',                                    &
    18621728                                   value = 'proleptic_gregorian' )
    1863        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1864                                    variable_name = 'time',                     &
    1865                                    attribute_name = 'bounds',                  &
     1729       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1730                                   variable_name = 'time',                                         &
     1731                                   attribute_name = 'bounds',                                      &
    18661732                                   value = 'time_bounds' )
    18671733!
    18681734!--    For vertical reference system
    1869        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1870                                    variable_name = 'vrs',                      &
    1871                                    attribute_name = char_long,                 &
     1735       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1736                                   variable_name = 'vrs',                                          &
     1737                                   attribute_name = char_long,                                     &
    18721738                                   value = 'vertical reference system' )
    1873        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1874                                    variable_name = 'vrs',                      &
    1875                                    attribute_name = 'system_name',             &
     1739       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1740                                   variable_name = 'vrs',                                          &
     1741                                   attribute_name = 'system_name',                                 &
    18761742                                   value = 'DHHN2016' )
    18771743!
    18781744!--    For z
    1879        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1880                                    variable_name = 'z',                        &
    1881                                    attribute_name = 'positive',                &
     1745       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1746                                   variable_name = 'z',                                            &
     1747                                   attribute_name = 'positive',                                    &
    18821748                                   value = 'up' )
    18831749!
    18841750!--    For coordinate reference system
    1885        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1886                                    variable_name = 'crs',                      &
    1887                                    attribute_name = 'epsg_code',               &
     1751       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1752                                   variable_name = 'crs',                                          &
     1753                                   attribute_name = 'epsg_code',                                   &
    18881754                                   value = coord_ref_sys%epsg_code )
    1889        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1890                                    variable_name = 'crs',                      &
    1891                                    attribute_name = 'false_easting',           &
     1755       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1756                                   variable_name = 'crs',                                          &
     1757                                   attribute_name = 'false_easting',                               &
    18921758                                   value = coord_ref_sys%false_easting )
    1893        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1894                                    variable_name = 'crs',                      &
    1895                                    attribute_name = 'false_northing',          &
     1759       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1760                                   variable_name = 'crs',                                          &
     1761                                   attribute_name = 'false_northing',                              &
    18961762                                   value = coord_ref_sys%false_northing )
    1897        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1898                                    variable_name = 'crs',                      &
    1899                                    attribute_name = 'grid_mapping_name',       &
     1763       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1764                                   variable_name = 'crs',                                          &
     1765                                   attribute_name = 'grid_mapping_name',                           &
    19001766                                   value = coord_ref_sys%grid_mapping_name )
    1901        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1902                                    variable_name = 'crs',                      &
    1903                                    attribute_name = 'inverse_flattening',      &
     1767       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1768                                   variable_name = 'crs',                                          &
     1769                                   attribute_name = 'inverse_flattening',                          &
    19041770                                   value = coord_ref_sys%inverse_flattening )
    1905        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1906                                    variable_name = 'crs',                      &
     1771       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1772                                   variable_name = 'crs',                                          &
    19071773                                   attribute_name = 'latitude_of_projection_origin',&
    19081774                                   value = coord_ref_sys%latitude_of_projection_origin )
    1909        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1910                                    variable_name = 'crs',                      &
    1911                                    attribute_name = char_long,                 &
     1775       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1776                                   variable_name = 'crs',                                          &
     1777                                   attribute_name = char_long,                                     &
    19121778                                   value = coord_ref_sys%long_name )
    1913        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1914                                    variable_name = 'crs',                      &
    1915                                    attribute_name = 'longitude_of_central_meridian', &
     1779       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1780                                   variable_name = 'crs',                                          &
     1781                                   attribute_name = 'longitude_of_central_meridian',               &
    19161782                                   value = coord_ref_sys%longitude_of_central_meridian )
    1917        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1918                                    variable_name = 'crs',                      &
    1919                                    attribute_name = 'longitude_of_prime_meridian', &
     1783       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1784                                   variable_name = 'crs',                                          &
     1785                                   attribute_name = 'longitude_of_prime_meridian',                 &
    19201786                                   value = coord_ref_sys%longitude_of_prime_meridian )
    1921        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1922                                    variable_name = 'crs',                      &
    1923                                    attribute_name = 'scale_factor_at_central_meridian', &
     1787       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1788                                   variable_name = 'crs',                                          &
     1789                                   attribute_name = 'scale_factor_at_central_meridian',            &
    19241790                                   value = coord_ref_sys%scale_factor_at_central_meridian )
    1925        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1926                                    variable_name = 'crs',                      &
    1927                                    attribute_name = 'semi_major_axis',         &
     1791       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1792                                   variable_name = 'crs',                                          &
     1793                                   attribute_name = 'semi_major_axis',                             &
    19281794                                   value = coord_ref_sys%semi_major_axis )
    1929        return_value = dom_def_att( vmea(l)%nc_filename,                        &
    1930                                    variable_name = 'crs',                      &
    1931                                    attribute_name = char_unit,                 &
     1795       return_value = dom_def_att( vmea(l)%nc_filename,                                            &
     1796                                   variable_name = 'crs',                                          &
     1797                                   attribute_name = char_unit,                                     &
    19321798                                   value = coord_ref_sys%units )
    19331799!
    1934 !--    In case of sampled soil quantities, define further dimensions and
    1935 !--    coordinates.
     1800!--    In case of sampled soil quantities, define further dimensions and coordinates.
    19361801       IF ( vmea(l)%soil_sampling )  THEN
    19371802!
     
    19421807          ENDDO
    19431808
    1944           return_value = dom_def_dim( vmea(l)%nc_filename,                     &
    1945                                       dimension_name = 'station_soil',         &
    1946                                       output_type = 'int32',                   &
    1947                                       bounds = (/1_iwp,vmea(l)%ns_soil_tot/),  &
     1809          return_value = dom_def_dim( vmea(l)%nc_filename,                                         &
     1810                                      dimension_name = 'station_soil',                             &
     1811                                      output_type = 'int32',                                       &
     1812                                      bounds = (/1_iwp,vmea(l)%ns_soil_tot/),                      &
    19481813                                      values_int32 = ndim )
    19491814          DEALLOCATE( ndim )
     
    19551820          ENDDO
    19561821
    1957           return_value = dom_def_dim( vmea(l)%nc_filename,                     &
    1958                                       dimension_name = 'ntime_soil',           &
    1959                                       output_type = 'int32',                   &
    1960                                       bounds = (/1_iwp,ntimesteps/),           &
     1822          return_value = dom_def_dim( vmea(l)%nc_filename,                                         &
     1823                                      dimension_name = 'ntime_soil',                               &
     1824                                      output_type = 'int32',                                       &
     1825                                      bounds = (/1_iwp,ntimesteps/),                               &
    19611826                                      values_int32 = ndim )
    19621827          DEALLOCATE( ndim )
     
    19641829!--       time for soil
    19651830          variable_name = 'time_soil'
    1966           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    1967                                       variable_name = variable_name,           &
    1968                                       dimension_names = (/'station_soil',      &
    1969                                                           'ntime_soil  '/),    &
     1831          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1832                                      variable_name = variable_name,                               &
     1833                                      dimension_names = (/'station_soil',                          &
     1834                                                          'ntime_soil  '/),                        &
    19701835                                      output_type = 'real32' )
    19711836!
    19721837!--       station_name for soil
    19731838          variable_name = 'station_name_soil'
    1974           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    1975                                       variable_name = variable_name,           &
    1976                                       dimension_names = (/ 'max_name_len',     &
    1977                                                            'station_soil' /),  &
     1839          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1840                                      variable_name = variable_name,                               &
     1841                                      dimension_names = (/ 'max_name_len',                         &
     1842                                                           'station_soil' /),                      &
    19781843                                      output_type = 'char' )
    19791844!
    19801845!--       z
    19811846          variable_name = 'z_soil'
    1982           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    1983                                       variable_name = variable_name,           &
    1984                                       dimension_names = (/'station_soil'/),    &
     1847          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1848                                      variable_name = variable_name,                               &
     1849                                      dimension_names = (/'station_soil'/),                        &
    19851850                                      output_type = 'real32' )
    19861851!
    19871852!--       station_h for soil
    19881853          variable_name = 'station_h_soil'
    1989           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    1990                                       variable_name = variable_name,           &
    1991                                       dimension_names = (/'station_soil'/),    &
     1854          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1855                                      variable_name = variable_name,                               &
     1856                                      dimension_names = (/'station_soil'/),                        &
    19921857                                      output_type = 'real32' )
    19931858!
    19941859!--       x soil
    19951860          variable_name = 'x_soil'
    1996           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    1997                                       variable_name = variable_name,           &
    1998                                       dimension_names = (/'station_soil'/),    &
     1861          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1862                                      variable_name = variable_name,                               &
     1863                                      dimension_names = (/'station_soil'/),                        &
    19991864                                      output_type = 'real32' )
    20001865!
    20011866!-        y soil
    20021867          variable_name = 'y_soil'
    2003           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    2004                                       variable_name = variable_name,           &
    2005                                       dimension_names = (/'station_soil'/),    &
     1868          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1869                                      variable_name = variable_name,                               &
     1870                                      dimension_names = (/'station_soil'/),                        &
    20061871                                      output_type = 'real32' )
    20071872!
    20081873!--       E-UTM soil
    20091874          variable_name = 'E_UTM_soil'
    2010           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    2011                                       variable_name = variable_name,           &
    2012                                       dimension_names = (/'station_soil'/),    &
     1875          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1876                                      variable_name = variable_name,                               &
     1877                                      dimension_names = (/'station_soil'/),                        &
    20131878                                      output_type = 'real32' )
    20141879!
    20151880!--       N-UTM soil
    20161881          variable_name = 'N_UTM_soil'
    2017           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    2018                                       variable_name = variable_name,           &
    2019                                       dimension_names = (/'station_soil'/),    &
     1882          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1883                                      variable_name = variable_name,                               &
     1884                                      dimension_names = (/'station_soil'/),                        &
    20201885                                      output_type = 'real32' )
    20211886!
    20221887!--       latitude soil
    20231888          variable_name = 'lat_soil'
    2024           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    2025                                       variable_name = variable_name,           &
    2026                                       dimension_names = (/'station_soil'/),    &
     1889          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1890                                      variable_name = variable_name,                               &
     1891                                      dimension_names = (/'station_soil'/),                        &
    20271892                                      output_type = 'real32' )
    20281893!
    20291894!--       longitude soil
    20301895          variable_name = 'lon_soil'
    2031           return_value = dom_def_var( vmea(l)%nc_filename,                     &
    2032                                       variable_name = variable_name,           &
    2033                                       dimension_names = (/'station_soil'/),    &
     1896          return_value = dom_def_var( vmea(l)%nc_filename,                                         &
     1897                                      variable_name = variable_name,                               &
     1898                                      dimension_names = (/'station_soil'/),                        &
    20341899                                      output_type = 'real32' )
    20351900!
    2036 !--       Set attributes for the coordinate variables. Note, not all coordinates
    2037 !--       have the same number of attributes.
     1901!--       Set attributes for the coordinate variables. Note, not all coordinates have the same
     1902!--       number of attributes.
    20381903!--       Units
    2039           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2040                                       variable_name = 'time_soil',             &
    2041                                       attribute_name = char_unit,              &
     1904          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1905                                      variable_name = 'time_soil',                                 &
     1906                                      attribute_name = char_unit,                                  &
    20421907                                      value = 'seconds since ' // origin_date_time )
    2043           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2044                                       variable_name = 'z_soil',                &
    2045                                       attribute_name = char_unit,              &
     1908          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1909                                      variable_name = 'z_soil',                                    &
     1910                                      attribute_name = char_unit,                                  &
    20461911                                      value = 'm' )
    2047           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2048                                       variable_name = 'station_h_soil',        &
    2049                                       attribute_name = char_unit,              &
     1912          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1913                                      variable_name = 'station_h_soil',                            &
     1914                                      attribute_name = char_unit,                                  &
    20501915                                      value = 'm' )
    2051           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2052                                       variable_name = 'x_soil',                &
    2053                                       attribute_name = char_unit,              &
     1916          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1917                                      variable_name = 'x_soil',                                    &
     1918                                      attribute_name = char_unit,                                  &
    20541919                                      value = 'm' )
    2055           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2056                                       variable_name = 'y_soil',                &
    2057                                       attribute_name = char_unit,              &
     1920          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1921                                      variable_name = 'y_soil',                                    &
     1922                                      attribute_name = char_unit,                                  &
    20581923                                      value = 'm' )
    2059           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2060                                       variable_name = 'E_UTM_soil',            &
    2061                                       attribute_name = char_unit,              &
     1924          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1925                                      variable_name = 'E_UTM_soil',                                &
     1926                                      attribute_name = char_unit,                                  &
    20621927                                      value = 'm' )
    2063           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2064                                       variable_name = 'N_UTM_soil',            &
    2065                                       attribute_name = char_unit,              &
     1928          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1929                                      variable_name = 'N_UTM_soil',                                &
     1930                                      attribute_name = char_unit,                                  &
    20661931                                      value = 'm' )
    2067           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2068                                       variable_name = 'lat_soil',              &
    2069                                       attribute_name = char_unit,              &
     1932          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1933                                      variable_name = 'lat_soil',                                  &
     1934                                      attribute_name = char_unit,                                  &
    20701935                                      value = 'degrees_north' )
    2071           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2072                                       variable_name = 'lon_soil',              &
    2073                                       attribute_name = char_unit,              &
     1936          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1937                                      variable_name = 'lon_soil',                                  &
     1938                                      attribute_name = char_unit,                                  &
    20741939                                      value = 'degrees_east' )
    20751940!
    20761941!--       Long name
    2077           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2078                                       variable_name = 'station_name_soil',     &
    2079                                       attribute_name = char_long,              &
     1942          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1943                                      variable_name = 'station_name_soil',                         &
     1944                                      attribute_name = char_long,                                  &
    20801945                                      value = 'station name')
    2081           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2082                                       variable_name = 'time_soil',             &
    2083                                       attribute_name = char_long,              &
     1946          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1947                                      variable_name = 'time_soil',                                 &
     1948                                      attribute_name = char_long,                                  &
    20841949                                      value = 'time')
    2085           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2086                                       variable_name = 'z_soil',                &
    2087                                       attribute_name = char_long,              &
     1950          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1951                                      variable_name = 'z_soil',                                    &
     1952                                      attribute_name = char_long,                                  &
    20881953                                      value = 'height above origin' )
    2089           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2090                                       variable_name = 'station_h_soil',        &
    2091                                       attribute_name = char_long,              &
     1954          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1955                                      variable_name = 'station_h_soil',                            &
     1956                                      attribute_name = char_long,                                  &
    20921957                                      value = 'surface altitude' )
    2093           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2094                                       variable_name = 'x_soil',                &
    2095                                       attribute_name = char_long,              &
     1958          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1959                                      variable_name = 'x_soil',                                    &
     1960                                      attribute_name = char_long,                                  &
    20961961                                      value = 'distance to origin in x-direction' )
    2097           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2098                                       variable_name = 'y_soil',                &
    2099                                       attribute_name = char_long,              &
     1962          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1963                                      variable_name = 'y_soil',                                    &
     1964                                      attribute_name = char_long,                                  &
    21001965                                      value = 'distance to origin in y-direction' )
    2101           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2102                                       variable_name = 'E_UTM_soil',            &
    2103                                       attribute_name = char_long,              &
     1966          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1967                                      variable_name = 'E_UTM_soil',                                &
     1968                                      attribute_name = char_long,                                  &
    21041969                                      value = 'easting' )
    2105           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2106                                       variable_name = 'N_UTM_soil',            &
    2107                                       attribute_name = char_long,              &
     1970          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1971                                      variable_name = 'N_UTM_soil',                                &
     1972                                      attribute_name = char_long,                                  &
    21081973                                      value = 'northing' )
    2109           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2110                                       variable_name = 'lat_soil',              &
    2111                                       attribute_name = char_long,              &
     1974          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1975                                      variable_name = 'lat_soil',                                  &
     1976                                      attribute_name = char_long,                                  &
    21121977                                      value = 'latitude' )
    2113           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2114                                       variable_name = 'lon_soil',              &
    2115                                       attribute_name = char_long,              &
     1978          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1979                                      variable_name = 'lon_soil',                                  &
     1980                                      attribute_name = char_long,                                  &
    21161981                                      value = 'longitude' )
    21171982!
    21181983!--       Standard name
    2119           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2120                                       variable_name = 'station_name_soil',     &
    2121                                       attribute_name = char_standard,          &
     1984          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1985                                      variable_name = 'station_name_soil',                         &
     1986                                      attribute_name = char_standard,                              &
    21221987                                      value = 'platform_name')
    2123           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2124                                       variable_name = 'time_soil',             &
    2125                                       attribute_name = char_standard,          &
     1988          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1989                                      variable_name = 'time_soil',                                 &
     1990                                      attribute_name = char_standard,                              &
    21261991                                      value = 'time')
    2127           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2128                                       variable_name = 'z_soil',                &
    2129                                       attribute_name = char_standard,          &
     1992          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1993                                      variable_name = 'z_soil',                                    &
     1994                                      attribute_name = char_standard,                              &
    21301995                                      value = 'height_above_mean_sea_level' )
    2131           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2132                                       variable_name = 'station_h_soil',        &
    2133                                       attribute_name = char_standard,          &
     1996          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     1997                                      variable_name = 'station_h_soil',                            &
     1998                                      attribute_name = char_standard,                              &
    21341999                                      value = 'surface_altitude' )
    2135           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2136                                       variable_name = 'E_UTM_soil',            &
    2137                                       attribute_name = char_standard,          &
     2000          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2001                                      variable_name = 'E_UTM_soil',                                &
     2002                                      attribute_name = char_standard,                              &
    21382003                                      value = 'projection_x_coordinate' )
    2139           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2140                                       variable_name = 'N_UTM_soil',            &
    2141                                       attribute_name = char_standard,          &
     2004          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2005                                      variable_name = 'N_UTM_soil',                                &
     2006                                      attribute_name = char_standard,                              &
    21422007                                      value = 'projection_y_coordinate' )
    2143           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2144                                       variable_name = 'lat_soil',              &
    2145                                       attribute_name = char_standard,          &
     2008          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2009                                      variable_name = 'lat_soil',                                  &
     2010                                      attribute_name = char_standard,                              &
    21462011                                      value = 'latitude' )
    2147           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2148                                       variable_name = 'lon_soil',              &
    2149                                       attribute_name = char_standard,          &
     2012          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2013                                      variable_name = 'lon_soil',                                  &
     2014                                      attribute_name = char_standard,                              &
    21502015                                      value = 'longitude' )
    21512016!
    21522017!--       Axis
    2153           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2154                                       variable_name = 'time_soil',             &
    2155                                       attribute_name = 'axis',                 &
     2018          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2019                                      variable_name = 'time_soil',                                 &
     2020                                      attribute_name = 'axis',                                     &
    21562021                                      value = 'T')
    2157           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2158                                       variable_name = 'z_soil',                &
    2159                                       attribute_name = 'axis',                 &
     2022          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2023                                      variable_name = 'z_soil',                                    &
     2024                                      attribute_name = 'axis',                                     &
    21602025                                      value = 'Z' )
    2161           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2162                                       variable_name = 'x_soil',                &
    2163                                       attribute_name = 'axis',                 &
     2026          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2027                                      variable_name = 'x_soil',                                    &
     2028                                      attribute_name = 'axis',                                     &
    21642029                                      value = 'X' )
    2165           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2166                                       variable_name = 'y_soil',                &
    2167                                       attribute_name = 'axis',                 &
     2030          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2031                                      variable_name = 'y_soil',                                    &
     2032                                      attribute_name = 'axis',                                     &
    21682033                                      value = 'Y' )
    21692034!
    21702035!--       Set further individual attributes for the coordinate variables.
    21712036!--       For station name soil
    2172           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2173                                       variable_name = 'station_name_soil',     &
    2174                                       attribute_name = 'cf_role',              &
     2037          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2038                                      variable_name = 'station_name_soil',                         &
     2039                                      attribute_name = 'cf_role',                                  &
    21752040                                      value = 'timeseries_id' )
    21762041!
    21772042!--       For time soil
    2178           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2179                                       variable_name = 'time_soil',             &
    2180                                       attribute_name = 'calendar',             &
     2043          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2044                                      variable_name = 'time_soil',                                 &
     2045                                      attribute_name = 'calendar',                                 &
    21812046                                      value = 'proleptic_gregorian' )
    2182           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2183                                       variable_name = 'time_soil',             &
    2184                                       attribute_name = 'bounds',               &
     2047          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2048                                      variable_name = 'time_soil',                                 &
     2049                                      attribute_name = 'bounds',                                   &
    21852050                                      value = 'time_bounds' )
    21862051!
    21872052!--       For z soil
    2188           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2189                                       variable_name = 'z_soil',                &
    2190                                       attribute_name = 'positive',             &
     2053          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2054                                      variable_name = 'z_soil',                                    &
     2055                                      attribute_name = 'positive',                                 &
    21912056                                      value = 'up' )
    21922057       ENDIF
     
    21962061          variable_name = TRIM( vmea(l)%var_atts(n)%name )
    21972062!
    2198 !--       In order to link the correct dimension names, atmosphere and soil
    2199 !--       variables need to be distinguished.
    2200           IF ( vmea(l)%soil_sampling  .AND.                                    &
     2063!--       In order to link the correct dimension names, atmosphere and soil variables need to be
     2064!--       distinguished.
     2065          IF ( vmea(l)%soil_sampling  .AND.                                                        &
    22012066               ANY( TRIM( vmea(l)%var_atts(n)%name) == soil_vars ) )  THEN
    22022067
    2203              return_value = dom_def_var( vmea(l)%nc_filename,                  &
    2204                                          variable_name = variable_name,        &
    2205                                          dimension_names = (/'station_soil',   &
    2206                                                              'ntime_soil  '/), &
     2068             return_value = dom_def_var( vmea(l)%nc_filename,                                      &
     2069                                         variable_name = variable_name,                            &
     2070                                         dimension_names = (/'station_soil',                       &
     2071                                                             'ntime_soil  '/),                     &
    22072072                                         output_type = 'real32' )
    22082073          ELSE
    22092074
    2210              return_value = dom_def_var( vmea(l)%nc_filename,                  &
    2211                                          variable_name = variable_name,        &
    2212                                          dimension_names = (/'station',        &
    2213                                                              'ntime  '/),      &
     2075             return_value = dom_def_var( vmea(l)%nc_filename,                                      &
     2076                                         variable_name = variable_name,                            &
     2077                                         dimension_names = (/'station',                            &
     2078                                                             'ntime  '/),                          &
    22142079                                         output_type = 'real32' )
    22152080          ENDIF
    22162081!
    2217 !--       Set variable attributes. Please note, for some variables not all
    2218 !--       attributes are defined, e.g. standard_name for the horizontal wind
    2219 !--       components.
     2082!--       Set variable attributes. Please note, for some variables not all attributes are defined,
     2083!--       e.g. standard_name for the horizontal wind components.
    22202084          CALL vm_set_attributes( vmea(l)%var_atts(n) )
    22212085
    22222086          IF ( vmea(l)%var_atts(n)%long_name /= 'none' )  THEN
    2223              return_value = dom_def_att( vmea(l)%nc_filename,                  &
    2224                                          variable_name = variable_name,        &
    2225                                          attribute_name = char_long,           &
     2087             return_value = dom_def_att( vmea(l)%nc_filename,                                      &
     2088                                         variable_name = variable_name,                            &
     2089                                         attribute_name = char_long,                               &
    22262090                                         value = TRIM( vmea(l)%var_atts(n)%long_name ) )
    22272091          ENDIF
    22282092          IF ( vmea(l)%var_atts(n)%standard_name /= 'none' )  THEN
    2229              return_value = dom_def_att( vmea(l)%nc_filename,                  &
    2230                                          variable_name = variable_name,        &
    2231                                          attribute_name = char_standard,       &
     2093             return_value = dom_def_att( vmea(l)%nc_filename,                                      &
     2094                                         variable_name = variable_name,                            &
     2095                                         attribute_name = char_standard,                           &
    22322096                                         value = TRIM( vmea(l)%var_atts(n)%standard_name ) )
    22332097          ENDIF
    22342098          IF ( vmea(l)%var_atts(n)%units /= 'none' )  THEN
    2235              return_value = dom_def_att( vmea(l)%nc_filename,                  &
    2236                                          variable_name = variable_name,        &
    2237                                          attribute_name = char_unit,           &
     2099             return_value = dom_def_att( vmea(l)%nc_filename,                                      &
     2100                                         variable_name = variable_name,                            &
     2101                                         attribute_name = char_unit,                               &
    22382102                                         value = TRIM( vmea(l)%var_atts(n)%units ) )
    22392103          ENDIF
    22402104
    2241           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2242                                       variable_name = variable_name,           &
    2243                                       attribute_name = 'grid_mapping',         &
     2105          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2106                                      variable_name = variable_name,                               &
     2107                                      attribute_name = 'grid_mapping',                             &
    22442108                                      value = TRIM( vmea(l)%var_atts(n)%grid_mapping ) )
    22452109
    2246           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2247                                       variable_name = variable_name,           &
    2248                                       attribute_name = 'coordinates',          &
     2110          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2111                                      variable_name = variable_name,                               &
     2112                                      attribute_name = 'coordinates',                              &
    22492113                                      value = TRIM( vmea(l)%var_atts(n)%coordinates ) )
    22502114
    2251           return_value = dom_def_att( vmea(l)%nc_filename,                     &
    2252                                       variable_name = variable_name,           &
    2253                                       attribute_name = char_fill,              &
     2115          return_value = dom_def_att( vmea(l)%nc_filename,                                         &
     2116                                      variable_name = variable_name,                               &
     2117                                      attribute_name = char_fill,                                  &
    22542118                                      value = REAL( vmea(l)%var_atts(n)%fill_value, KIND=4 ) )
    22552119
     
    22612125 END SUBROUTINE vm_init_output
    22622126
    2263 !------------------------------------------------------------------------------!
     2127!--------------------------------------------------------------------------------------------------!
    22642128! Description:
    22652129! ------------
    22662130!> Parallel NetCDF output via data-output module.
    2267 !------------------------------------------------------------------------------!
     2131!--------------------------------------------------------------------------------------------------!
    22682132 SUBROUTINE vm_data_output
    22692133
    2270     CHARACTER(LEN=100) ::  variable_name !< name of output variable
    2271     CHARACTER(LEN=maximum_name_length), DIMENSION(:), ALLOCATABLE :: station_name !< string for station name, consecutively ordered
     2134    CHARACTER(LEN=100) ::  variable_name  !< name of output variable
     2135    CHARACTER(LEN=maximum_name_length), DIMENSION(:), ALLOCATABLE :: station_name  !< string for station name, consecutively ordered
    22722136
    22732137    CHARACTER(LEN=1), DIMENSION(:,:), ALLOCATABLE, TARGET ::  output_values_2d_char_target  !< target for output name arrays
     
    22782142    INTEGER(iwp)       ::  nn            !< loop index for number of characters in a name
    22792143    INTEGER            ::  return_value  !< returned status value of called function
    2280 
    22812144    INTEGER(iwp)       ::  t_ind         !< time index
    22822145
    2283     REAL(wp), DIMENSION(:), ALLOCATABLE           ::  oro_rel                  !< relative altitude of model surface
    2284     REAL(wp), DIMENSION(:), POINTER               ::  output_values_1d_pointer !< pointer for 1d output array
    2285     REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET   ::  output_values_1d_target  !< target for 1d output array
    2286     REAL(wp), DIMENSION(:,:), POINTER             ::  output_values_2d_pointer !< pointer for 2d output array
    2287     REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET ::  output_values_2d_target  !< target for 2d output array
     2146    REAL(wp), DIMENSION(:), ALLOCATABLE           ::  oro_rel                   !< relative altitude of model surface
     2147    REAL(wp), DIMENSION(:), POINTER               ::  output_values_1d_pointer  !< pointer for 1d output array
     2148    REAL(wp), DIMENSION(:), ALLOCATABLE, TARGET   ::  output_values_1d_target   !< target for 1d output array
     2149    REAL(wp), DIMENSION(:,:), POINTER             ::  output_values_2d_pointer  !< pointer for 2d output array
     2150    REAL(wp), DIMENSION(:,:), ALLOCATABLE, TARGET ::  output_values_2d_target   !< target for 2d output array
    22882151
    22892152    CALL cpu_log( log_point_s(26), 'VM output', 'start' )
     
    23012164!
    23022165!--       Output of Easting coordinate. Before output, recalculate EUTM.
    2303           output_values_1d_target = init_model%origin_x                        &
    2304                     + REAL( vmea(l)%i(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dx &
    2305                     * COS( init_model%rotation_angle * pi / 180.0_wp )         &
    2306                     + REAL( vmea(l)%j(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dy &
     2166          output_values_1d_target = init_model%origin_x                                            &
     2167                    + REAL( vmea(l)%i(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dx                     &
     2168                    * COS( init_model%rotation_angle * pi / 180.0_wp )                             &
     2169                    + REAL( vmea(l)%j(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dy                     &
    23072170                    * SIN( init_model%rotation_angle * pi / 180.0_wp )
    23082171
    23092172          output_values_1d_pointer => output_values_1d_target
    23102173
    2311           return_value =                                                       &
    2312                   dom_write_var( vmea(l)%nc_filename,                          &
    2313                                  'E_UTM',                                      &
    2314                                  values_realwp_1d = output_values_1d_pointer,  &
    2315                                  bounds_start = (/vmea(l)%start_coord_a/),     &
     2174          return_value =                                                                           &
     2175                  dom_write_var( vmea(l)%nc_filename,                                              &
     2176                                 'E_UTM',                                                          &
     2177                                 values_realwp_1d = output_values_1d_pointer,                      &
     2178                                 bounds_start = (/vmea(l)%start_coord_a/),                         &
    23162179                                 bounds_end   = (/vmea(l)%end_coord_a  /) )
    23172180!
    23182181!--       Output of Northing coordinate. Before output, recalculate NUTM.
    2319           output_values_1d_target = init_model%origin_y                        &
    2320                     - REAL( vmea(l)%i(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dx &
    2321                     * SIN( init_model%rotation_angle * pi / 180.0_wp )         &
    2322                     + REAL( vmea(l)%j(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dy &
     2182          output_values_1d_target = init_model%origin_y                                            &
     2183                    - REAL( vmea(l)%i(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dx                     &
     2184                    * SIN( init_model%rotation_angle * pi / 180.0_wp )                             &
     2185                    + REAL( vmea(l)%j(1:vmea(l)%ns) + 0.5_wp, KIND = wp ) * dy                     &
    23232186                    * COS( init_model%rotation_angle * pi / 180.0_wp )
    23242187
    23252188          output_values_1d_pointer => output_values_1d_target
    2326           return_value =                                                       &
    2327                   dom_write_var( vmea(l)%nc_filename,                          &
    2328                                  'N_UTM',                                      &
    2329                                  values_realwp_1d = output_values_1d_pointer,  &
    2330                                  bounds_start = (/vmea(l)%start_coord_a/),     &
     2189          return_value =                                                                           &
     2190                  dom_write_var( vmea(l)%nc_filename,                                              &
     2191                                 'N_UTM',                                                          &
     2192                                 values_realwp_1d = output_values_1d_pointer,                      &
     2193                                 bounds_start = (/vmea(l)%start_coord_a/),                         &
    23312194                                 bounds_end   = (/vmea(l)%end_coord_a  /) )
    23322195!
    23332196!--       Output of relative height coordinate.
    2334 !--       Before this is output, first define the relative orographie height
    2335 !--       and add this to z.
     2197!--       Before this is output, first define the relative orographie height and add this to z.
    23362198          ALLOCATE( oro_rel(1:vmea(l)%ns) )
    23372199          DO  n = 1, vmea(l)%ns
     
    23412203          output_values_1d_target = vmea(l)%zar(1:vmea(l)%ns) + oro_rel(:)
    23422204          output_values_1d_pointer => output_values_1d_target
    2343           return_value =                                                       &
    2344                   dom_write_var( vmea(l)%nc_filename,                          &
    2345                                  'z',                                          &
    2346                                  values_realwp_1d = output_values_1d_pointer,  &
    2347                                  bounds_start = (/vmea(l)%start_coord_a/),     &
     2205          return_value =                                                                           &
     2206                  dom_write_var( vmea(l)%nc_filename,                                              &
     2207                                 'z',                                                              &
     2208                                 values_realwp_1d = output_values_1d_pointer,                      &
     2209                                 bounds_start = (/vmea(l)%start_coord_a/),                         &
    23482210                                 bounds_end   = (/vmea(l)%end_coord_a  /) )
    23492211!
    2350 !--       Write surface altitude for the station. Note, since z is already
    2351 !--       a relative observation height, station_h must be zero, in order
    2352 !--       to obtain the observation level.
     2212!--       Write surface altitude for the station. Note, since z is already a relative observation
     2213!--       height, station_h must be zero, in order to obtain the observation level.
    23532214          output_values_1d_target = oro_rel(:)
    23542215          output_values_1d_pointer => output_values_1d_target
    2355           return_value =                                                       &
    2356                   dom_write_var( vmea(l)%nc_filename,                          &
    2357                                  'station_h',                                  &
    2358                                  values_realwp_1d = output_values_1d_pointer,  &
    2359                                  bounds_start = (/vmea(l)%start_coord_a/),     &
     2216          return_value =                                                                           &
     2217                  dom_write_var( vmea(l)%nc_filename,                                              &
     2218                                 'station_h',                                                      &
     2219                                 values_realwp_1d = output_values_1d_pointer,                      &
     2220                                 bounds_start = (/vmea(l)%start_coord_a/),                         &
    23602221                                 bounds_end   = (/vmea(l)%end_coord_a  /) )
    23612222
     
    23782239          output_values_2d_char_pointer => output_values_2d_char_target
    23792240
    2380           return_value =                                                       &
    2381                   dom_write_var( vmea(l)%nc_filename,                          &
    2382                                  'station_name',                               &
    2383                                  values_char_2d = output_values_2d_char_pointer,&
    2384                                  bounds_start = (/ 1,                   vmea(l)%start_coord_a /),&
     2241          return_value =                                                                           &
     2242                  dom_write_var( vmea(l)%nc_filename,                                              &
     2243                                 'station_name',                                                   &
     2244                                 values_char_2d = output_values_2d_char_pointer,                   &
     2245                                 bounds_start = (/ 1,                   vmea(l)%start_coord_a /),  &
    23852246                                 bounds_end   = (/ maximum_name_length, vmea(l)%end_coord_a /) )
    23862247
     
    23882249          DEALLOCATE( output_values_2d_char_target )
    23892250!
    2390 !--       In case of sampled soil quantities, output also the respective
    2391 !--       coordinate arrays.
     2251!--       In case of sampled soil quantities, output also the respective coordinate arrays.
    23922252          IF ( vmea(l)%soil_sampling )  THEN
    23932253             ALLOCATE( output_values_1d_target(vmea(l)%start_coord_s:vmea(l)%end_coord_s) )
    23942254!
    23952255!--          Output of Easting coordinate. Before output, recalculate EUTM.
    2396              output_values_1d_target = init_model%origin_x                     &
    2397                + REAL( vmea(l)%i(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dx &
    2398                * COS( init_model%rotation_angle * pi / 180.0_wp )              &
    2399                + REAL( vmea(l)%j(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dy &
     2256             output_values_1d_target = init_model%origin_x                                         &
     2257               + REAL( vmea(l)%i(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dx                     &
     2258               * COS( init_model%rotation_angle * pi / 180.0_wp )                                  &
     2259               + REAL( vmea(l)%j(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dy                     &
    24002260               * SIN( init_model%rotation_angle * pi / 180.0_wp )
    24012261             output_values_1d_pointer => output_values_1d_target
    2402              return_value =                                                    &
    2403                   dom_write_var( vmea(l)%nc_filename,                          &
    2404                                  'E_UTM_soil',                                 &
    2405                                  values_realwp_1d = output_values_1d_pointer,  &
    2406                                  bounds_start = (/vmea(l)%start_coord_s/),     &
     2262             return_value =                                                                        &
     2263                  dom_write_var( vmea(l)%nc_filename,                                              &
     2264                                 'E_UTM_soil',                                                     &
     2265                                 values_realwp_1d = output_values_1d_pointer,                      &
     2266                                 bounds_start = (/vmea(l)%start_coord_s/),                         &
    24072267                                 bounds_end   = (/vmea(l)%end_coord_s  /) )
    24082268!
    24092269!--          Output of Northing coordinate. Before output, recalculate NUTM.
    2410              output_values_1d_target = init_model%origin_y                     &
    2411                - REAL( vmea(l)%i(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dx &
    2412                * SIN( init_model%rotation_angle * pi / 180.0_wp )              &
    2413                + REAL( vmea(l)%j(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dy &
     2270             output_values_1d_target = init_model%origin_y                                         &
     2271               - REAL( vmea(l)%i(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dx                     &
     2272               * SIN( init_model%rotation_angle * pi / 180.0_wp )                                  &
     2273               + REAL( vmea(l)%j(1:vmea(l)%ns_soil) + 0.5_wp, KIND = wp ) * dy                     &
    24142274               * COS( init_model%rotation_angle * pi / 180.0_wp )
    24152275
    24162276             output_values_1d_pointer => output_values_1d_target
    2417              return_value =                                                    &
    2418                   dom_write_var( vmea(l)%nc_filename,                          &
    2419                                  'N_UTM_soil',                                 &
    2420                                  values_realwp_1d = output_values_1d_pointer,  &
    2421                                  bounds_start = (/vmea(l)%start_coord_s/),     &
     2277             return_value =                                                                        &
     2278                  dom_write_var( vmea(l)%nc_filename,                                              &
     2279                                 'N_UTM_soil',                                                     &
     2280                                 values_realwp_1d = output_values_1d_pointer,                      &
     2281                                 bounds_start = (/vmea(l)%start_coord_s/),                         &
    24222282                                 bounds_end   = (/vmea(l)%end_coord_s  /) )
    24232283!
    24242284!--          Output of relative height coordinate.
    2425 !--          Before this is output, first define the relative orographie height
    2426 !--          and add this to z.
     2285!--          Before this is output, first define the relative orographie height and add this to z.
    24272286             ALLOCATE( oro_rel(1:vmea(l)%ns_soil) )
    24282287             DO  n = 1, vmea(l)%ns_soil
     
    24322291             output_values_1d_target = vmea(l)%depth(1:vmea(l)%ns_soil) + oro_rel(:)
    24332292             output_values_1d_pointer => output_values_1d_target
    2434              return_value =                                                    &
    2435                   dom_write_var( vmea(l)%nc_filename,                          &
    2436                                  'z_soil',                                     &
    2437                                  values_realwp_1d = output_values_1d_pointer,  &
    2438                                  bounds_start = (/vmea(l)%start_coord_s/),     &
     2293             return_value =                                                                        &
     2294                  dom_write_var( vmea(l)%nc_filename,                                              &
     2295                                 'z_soil',                                                         &
     2296                                 values_realwp_1d = output_values_1d_pointer,                      &
     2297                                 bounds_start = (/vmea(l)%start_coord_s/),                         &
    24392298                                 bounds_end   = (/vmea(l)%end_coord_s  /) )
    24402299!
    2441 !--          Write surface altitude for the station. Note, since z is already
    2442 !--          a relative observation height, station_h must be zero, in order
    2443 !--          to obtain the observation level.
     2300!--          Write surface altitude for the station. Note, since z is already a relative observation
     2301!--          height, station_h must be zero, in order to obtain the observation level.
    24442302             output_values_1d_target = oro_rel(:)
    24452303             output_values_1d_pointer => output_values_1d_target
    2446              return_value =                                                    &
    2447                   dom_write_var( vmea(l)%nc_filename,                          &
    2448                                  'station_h_soil',                             &
    2449                                  values_realwp_1d = output_values_1d_pointer,  &
    2450                                  bounds_start = (/vmea(l)%start_coord_s/),     &
     2304             return_value =                                                                        &
     2305                  dom_write_var( vmea(l)%nc_filename,                                              &
     2306                                 'station_h_soil',                                                 &
     2307                                 values_realwp_1d = output_values_1d_pointer,                      &
     2308                                 bounds_start = (/vmea(l)%start_coord_s/),                         &
    24512309                                 bounds_end   = (/vmea(l)%end_coord_s  /) )
    24522310
     
    24562314!--          Write station name
    24572315             ALLOCATE ( station_name(vmea(l)%start_coord_s:vmea(l)%end_coord_s) )
    2458              ALLOCATE ( output_values_2d_char_target(vmea(l)%start_coord_s:vmea(l)%end_coord_s, &
     2316             ALLOCATE ( output_values_2d_char_target(vmea(l)%start_coord_s:vmea(l)%end_coord_s,    &
    24592317                                                     1:maximum_name_length) )
    24602318
     
    24682326             output_values_2d_char_pointer => output_values_2d_char_target
    24692327
    2470              return_value =                                                    &
    2471                   dom_write_var( vmea(l)%nc_filename,                          &
    2472                                  'station_name_soil',                          &
    2473                                  values_char_2d = output_values_2d_char_pointer,&
    2474                                  bounds_start = (/ 1,                   vmea(l)%start_coord_s /),&
     2328             return_value =                                                                        &
     2329                  dom_write_var( vmea(l)%nc_filename,                                              &
     2330                                 'station_name_soil',                                              &
     2331                                 values_char_2d = output_values_2d_char_pointer,                   &
     2332                                 bounds_start = (/ 1,                   vmea(l)%start_coord_s /),  &
    24752333                                 bounds_end   = (/ maximum_name_length, vmea(l)%end_coord_s   /) )
    24762334
     
    24962354!--    Write output variables. Distinguish between atmosphere and soil variables.
    24972355       DO  n = 1, vmea(l)%nmeas
    2498           IF ( vmea(l)%soil_sampling  .AND.                                    &
     2356          IF ( vmea(l)%soil_sampling  .AND.                                                        &
    24992357            ANY( TRIM( vmea(l)%var_atts(n)%name) == soil_vars ) )  THEN
    25002358!
     
    25052363             output_values_2d_pointer => output_values_2d_target
    25062364
    2507              return_value = dom_write_var( vmea(l)%nc_filename,                &
    2508                                            variable_name,                      &
     2365             return_value = dom_write_var( vmea(l)%nc_filename,                                    &
     2366                                           variable_name,                                          &
    25092367                                           values_realwp_2d = output_values_2d_pointer, &
    2510                                            bounds_start = (/vmea(l)%start_coord_s, t_ind/), &
     2368                                           bounds_start = (/vmea(l)%start_coord_s, t_ind/),        &
    25112369                                           bounds_end   = (/vmea(l)%end_coord_s, t_ind /) )
    25122370
     
    25142372             output_values_2d_target(t_ind,:) = vmea(l)%measured_vars_soil(:,n)
    25152373             output_values_2d_pointer => output_values_2d_target
    2516              return_value =                                                    &
    2517                       dom_write_var( vmea(l)%nc_filename,                      &
    2518                                      variable_name,                            &
    2519                                      values_realwp_2d = output_values_2d_pointer, &
    2520                                      bounds_start = (/vmea(l)%start_coord_s, t_ind/), &
     2374             return_value =                                                                        &
     2375                      dom_write_var( vmea(l)%nc_filename,                                          &
     2376                                     variable_name,                                                &
     2377                                     values_realwp_2d = output_values_2d_pointer,                  &
     2378                                     bounds_start = (/vmea(l)%start_coord_s, t_ind/),              &
    25212379                                     bounds_end   = (/vmea(l)%end_coord_s, t_ind  /) )
    25222380             DEALLOCATE( output_values_2d_target )
     
    25292387             output_values_2d_pointer => output_values_2d_target
    25302388
    2531              return_value = dom_write_var( vmea(l)%nc_filename,                &
    2532                                            variable_name,                      &
    2533                                            values_realwp_2d = output_values_2d_pointer, &
    2534                                            bounds_start = (/vmea(l)%start_coord_a, t_ind/), &
     2389             return_value = dom_write_var( vmea(l)%nc_filename,                                    &
     2390                                           variable_name,                                          &
     2391                                           values_realwp_2d = output_values_2d_pointer,            &
     2392                                           bounds_start = (/vmea(l)%start_coord_a, t_ind/),        &
    25352393                                           bounds_end   = (/vmea(l)%end_coord_a, t_ind/) )
    25362394
     
    25392397             output_values_2d_target(t_ind,:) = vmea(l)%measured_vars(:,n)
    25402398             output_values_2d_pointer => output_values_2d_target
    2541              return_value =                                                    &
    2542                       dom_write_var( vmea(l)%nc_filename,                      &
    2543                                      variable_name,                            &
    2544                                      values_realwp_2d = output_values_2d_pointer, &
    2545                                      bounds_start = (/ vmea(l)%start_coord_a, t_ind /), &
     2399             return_value =                                                                        &
     2400                      dom_write_var( vmea(l)%nc_filename,                                          &
     2401                                     variable_name,                                                &
     2402                                     values_realwp_2d = output_values_2d_pointer,                  &
     2403                                     bounds_start = (/ vmea(l)%start_coord_a, t_ind /),            &
    25462404                                     bounds_end   = (/ vmea(l)%end_coord_a, t_ind /) )
    25472405
     
    25582416
    25592417
    2560   END SUBROUTINE vm_data_output
    2561 
    2562 !------------------------------------------------------------------------------!
     2418 END SUBROUTINE vm_data_output
     2419
     2420!--------------------------------------------------------------------------------------------------!
    25632421! Description:
    25642422! ------------
    25652423!> Sampling of the actual quantities along the observation coordinates
    2566 !------------------------------------------------------------------------------!
    2567   SUBROUTINE vm_sampling
    2568 
    2569     USE radiation_model_mod,                                                   &
     2424!--------------------------------------------------------------------------------------------------!
     2425 SUBROUTINE vm_sampling
     2426
     2427    USE radiation_model_mod,                                                                       &
    25702428        ONLY:  radiation
    25712429
    2572     USE surface_mod,                                                           &
    2573         ONLY:  surf_def_h,                                                     &
    2574                surf_lsm_h,                                                     &
     2430    USE surface_mod,                                                                               &
     2431        ONLY:  surf_def_h,                                                                         &
     2432               surf_lsm_h,                                                                         &
    25752433               surf_usm_h
    25762434
     
    25852443     INTEGER(iwp) ::  nn        !< running index over the number of chemcal species
    25862444
    2587      LOGICAL ::  match_lsm !< flag indicating natural-type surface
    2588      LOGICAL ::  match_usm !< flag indicating urban-type surface
    2589 
    2590      REAL(wp) ::  e_s      !< saturation water vapor pressure
    2591      REAL(wp) ::  q_s      !< saturation mixing ratio
    2592      REAL(wp) ::  q_wv     !< mixing ratio
     2445     LOGICAL ::  match_lsm  !< flag indicating natural-type surface
     2446     LOGICAL ::  match_usm  !< flag indicating urban-type surface
     2447
     2448     REAL(wp) ::  e_s   !< saturation water vapor pressure
     2449     REAL(wp) ::  q_s   !< saturation mixing ratio
     2450     REAL(wp) ::  q_wv  !< mixing ratio
    25932451
    25942452     CALL cpu_log( log_point_s(27), 'VM sampling', 'start' )
     
    25982456!
    25992457!--     At the beginning, set _FillValues
    2600         IF ( ALLOCATED( vmea(l)%measured_vars      ) )                         &
    2601            vmea(l)%measured_vars      = vmea(l)%fillout
    2602         IF ( ALLOCATED( vmea(l)%measured_vars_soil ) )                         &
    2603            vmea(l)%measured_vars_soil = vmea(l)%fillout
     2458        IF ( ALLOCATED( vmea(l)%measured_vars ) ) vmea(l)%measured_vars = vmea(l)%fillout
     2459        IF ( ALLOCATED( vmea(l)%measured_vars_soil ) ) vmea(l)%measured_vars_soil = vmea(l)%fillout
    26042460!
    26052461!--     Loop over all variables measured at this site.
     
    26242480                       j = vmea(l)%j(m)
    26252481                       i = vmea(l)%i(m)
    2626                        vmea(l)%measured_vars(m,n) = pt(k,j,i) * exner( k )     &
    2627                                                   - degc_to_k
     2482                       vmea(l)%measured_vars(m,n) = pt(k,j,i) * exner( k ) - degc_to_k
    26282483                    ENDDO
    26292484                 ENDIF
     
    26472502                       j = vmea(l)%j(m)
    26482503                       i = vmea(l)%i(m)
    2649                        vmea(l)%measured_vars(m,n) = ( q(k,j,i)                 &
    2650                                                     / ( 1.0_wp - q(k,j,i) ) )  &
    2651                                                   * rho_air(k)
     2504                       vmea(l)%measured_vars(m,n) = ( q(k,j,i) / ( 1.0_wp - q(k,j,i) ) ) * rho_air(k)
    26522505                    ENDDO
    26532506                 ENDIF
     
    26592512!                        j = vmea(l)%j(m)
    26602513!                        i = vmea(l)%i(m)
    2661 !                        vmea(l)%measured_vars(m,n) = ( q(k,j,i)                 &
    2662 !                                                     / ( 1.0_wp - q(k,j,i) ) )  &
    2663 !                                                   * rho_air(k)
     2514!                        vmea(l)%measured_vars(m,n) = ( q(k,j,i) / ( 1.0_wp - q(k,j,i) ) )          &
     2515!                                                     * rho_air(k)
    26642516!                     ENDDO
    26652517                 ENDIF
     
    26722524                       i = vmea(l)%i(m)
    26732525!
    2674 !--                    Calculate actual temperature, water vapor saturation
    2675 !--                    pressure, and based on this the saturation mixing ratio.
     2526!--                    Calculate actual temperature, water vapor saturation pressure and, based on
     2527!--                    this, the saturation mixing ratio.
    26762528                       e_s  = magnus( exner(k) * pt(k,j,i) )
    26772529                       q_s  = rd_d_rv * e_s / ( hyp(k) - e_s )
     
    27112563                    j = vmea(l)%j(m)
    27122564                    i = vmea(l)%i(m)
    2713                     vmea(l)%measured_vars(m,n) = SQRT(                         &
    2714                                    ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) )**2 + &
    2715                                    ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) )**2   &
     2565                    vmea(l)%measured_vars(m,n) = SQRT(                                             &
     2566                                                 ( 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) )**2 +      &
     2567                                                 ( 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) )**2         &
    27162568                                                     )
    27172569                 ENDDO
     
    27232575                    i = vmea(l)%i(m)
    27242576
    2725                     vmea(l)%measured_vars(m,n) = 180.0_wp + 180.0_wp / pi      &
    2726                                                * ATAN2(                        &
    2727                                           0.5_wp * ( v(k,j,i) + v(k,j+1,i) ),  &
    2728                                           0.5_wp * ( u(k,j,i) + u(k,j,i+1) )   &
    2729                                                       )
     2577                    vmea(l)%measured_vars(m,n) = 180.0_wp + 180.0_wp / pi * ATAN2(                 &
     2578                                                 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ),               &
     2579                                                 0.5_wp * ( u(k,j,i) + u(k,j,i+1) )                &
     2580                                                                                  )
    27302581                 ENDDO
    27312582
     
    27352586                    j = vmea(l)%j(m)
    27362587                    i = vmea(l)%i(m)
    2737                     vmea(l)%measured_vars(m,n) = 0.5_wp *                      &
    2738                                                  ( u(k,j,i) + u(k,j,i+1) ) *   &
    2739                                                    pt(k,j,i)
     2588                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) * pt(k,j,i)
    27402589                 ENDDO
    27412590
     
    27452594                    j = vmea(l)%j(m)
    27462595                    i = vmea(l)%i(m)
    2747                     vmea(l)%measured_vars(m,n) = 0.5_wp *                      &
    2748                                                  ( v(k,j,i) + v(k,j+1,i) ) *   &
    2749                                                    pt(k,j,i)
     2596                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) * pt(k,j,i)
    27502597                 ENDDO
    27512598
     
    27552602                    j = vmea(l)%j(m)
    27562603                    i = vmea(l)%i(m)
    2757                     vmea(l)%measured_vars(m,n) = 0.5_wp *                      &
    2758                                                  ( w(k-1,j,i) + w(k,j,i) ) *   &
    2759                                                    pt(k,j,i)
     2604                    vmea(l)%measured_vars(m,n) = 0.5_wp * ( w(k-1,j,i) + w(k,j,i) ) * pt(k,j,i)
    27602605                 ENDDO
    27612606
     
    27662611                       j = vmea(l)%j(m)
    27672612                       i = vmea(l)%i(m)
    2768                        vmea(l)%measured_vars(m,n) = 0.5_wp *                   &
    2769                                                     ( u(k,j,i) + u(k,j,i+1) ) *&
    2770                                                       q(k,j,i)
     2613                       vmea(l)%measured_vars(m,n) = 0.5_wp * ( u(k,j,i) + u(k,j,i+1) ) * q(k,j,i)
    27712614                    ENDDO
    27722615                 ENDIF
     
    27782621                       j = vmea(l)%j(m)
    27792622                       i = vmea(l)%i(m)
    2780                        vmea(l)%measured_vars(m,n) = 0.5_wp *                   &
    2781                                                     ( v(k,j,i) + v(k,j+1,i) ) *&
    2782                                                       q(k,j,i)
     2623                       vmea(l)%measured_vars(m,n) = 0.5_wp * ( v(k,j,i) + v(k,j+1,i) ) * q(k,j,i)
    27832624                    ENDDO
    27842625                 ENDIF
     
    27902631                       j = vmea(l)%j(m)
    27912632                       i = vmea(l)%i(m)
    2792                        vmea(l)%measured_vars(m,n) = 0.5_wp *                   &
    2793                                                     ( w(k-1,j,i) + w(k,j,i) ) *&
    2794                                                       q(k,j,i)
     2633                       vmea(l)%measured_vars(m,n) = 0.5_wp * ( w(k-1,j,i) + w(k,j,i) ) * q(k,j,i)
    27952634                    ENDDO
    27962635                 ENDIF
     
    28012640                    j = vmea(l)%j(m)
    28022641                    i = vmea(l)%i(m)
    2803                     vmea(l)%measured_vars(m,n) = 0.25_wp *                     &
    2804                                                  ( w(k-1,j,i) + w(k,j,i) ) *   &
    2805                                                  ( u(k,j,i)   + u(k,j,i+1) )
     2642                    vmea(l)%measured_vars(m,n) = 0.25_wp * ( w(k-1,j,i) + w(k,j,i) ) *             &
     2643                                                           ( u(k,j,i)   + u(k,j,i+1) )
    28062644                 ENDDO
    28072645
     
    28112649                    j = vmea(l)%j(m)
    28122650                    i = vmea(l)%i(m)
    2813                     vmea(l)%measured_vars(m,n) = 0.25_wp *                     &
    2814                                                  ( w(k-1,j,i) + w(k,j,i) ) *   &
    2815                                                  ( v(k,j,i)   + v(k,j+1,i) )
     2651                    vmea(l)%measured_vars(m,n) = 0.25_wp * ( w(k-1,j,i) + w(k,j,i) ) *             &
     2652                                                           ( v(k,j,i)   + v(k,j+1,i) )
    28162653                 ENDDO
    28172654
     
    28212658                    j = vmea(l)%j(m)
    28222659                    i = vmea(l)%i(m)
    2823                     vmea(l)%measured_vars(m,n) = 0.25_wp *                     &
    2824                                                  ( u(k,j,i)   + u(k,j,i+1) ) * &
    2825                                                  ( v(k,j,i)   + v(k,j+1,i) )
     2660                    vmea(l)%measured_vars(m,n) = 0.25_wp * ( u(k,j,i)   + u(k,j,i+1) ) *           &
     2661                                                           ( v(k,j,i)   + v(k,j+1,i) )
    28262662                 ENDDO
    28272663!
    2828 !--           Chemistry variables. List of variables may need extension.
    2829 !--           Note, gas species in PALM are in ppm and no distinction is made
    2830 !--           between mole-fraction and concentration quantities (all are
    2831 !--           output in ppm so far).
    2832               CASE ( 'mcpm1', 'mcpm2p5', 'mcpm10', 'mfno', 'mfno2',            &
    2833                      'mcno', 'mcno2', 'tro3' )
     2664!--           Chemistry variables. List of variables that may need extension. Note, gas species in
     2665!--           PALM are in ppm and no distinction is made between mole-fraction and concentration
     2666!--           quantities (all are output in ppm so far).
     2667              CASE ( 'mcpm1', 'mcpm2p5', 'mcpm10', 'mfno', 'mfno2', 'mcno', 'mcno2', 'tro3' )
    28342668                 IF ( air_chemistry )  THEN
    28352669!
     
    28372671!--                 list, in order to get the internal name of the variable.
    28382672                    DO  nn = 1, UBOUND( chem_vars, 2 )
    2839                        IF ( TRIM( vmea(l)%var_atts(n)%name ) ==                &
     2673                       IF ( TRIM( vmea(l)%var_atts(n)%name ) ==                                    &
    28402674                            TRIM( chem_vars(0,nn) ) )  ind_chem = nn
    28412675                    ENDDO
    28422676!
    2843 !--                 Run loop over all chemical species, if the measured
    2844 !--                 variable matches the interal name, sample the variable.
    2845 !--                 Note, nvar as a chemistry-module variable.
     2677!--                 Run loop over all chemical species, if the measured variable matches the interal
     2678!--                 name, sample the variable. Note, nvar as a chemistry-module variable.
    28462679                    DO  nn = 1, nvar
    2847                        IF ( TRIM( chem_vars(1,ind_chem) ) ==                   &
    2848                             TRIM( chem_species(nn)%name ) )  THEN
     2680                       IF ( TRIM( chem_vars(1,ind_chem) ) == TRIM( chem_species(nn)%name ) )  THEN
    28492681                          DO  m = 1, vmea(l)%ns
    28502682                             k = vmea(l)%k(m)
    28512683                             j = vmea(l)%j(m)
    28522684                             i = vmea(l)%i(m)
    2853                              vmea(l)%measured_vars(m,n) =                      &
    2854                                                    chem_species(nn)%conc(k,j,i)
     2685                             vmea(l)%measured_vars(m,n) = chem_species(nn)%conc(k,j,i)
    28552686                          ENDDO
    28562687                       ENDIF
     
    28612692                 DO  m = 1, vmea(l)%ns
    28622693!
    2863 !--                 Surface data is only available on inner subdomains, not
    2864 !--                 on ghost points. Hence, limit the indices.
     2694!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
     2695!--                 limit the indices.
    28652696                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    28662697                    j = MERGE( j           , nyn, j            < nyn )
     
    28682699                    i = MERGE( i           , nxr, i            < nxr )
    28692700
    2870                     DO  mm = surf_def_h(0)%start_index(j,i),                   &
    2871                              surf_def_h(0)%end_index(j,i)
     2701                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
    28722702                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%us(mm)
    28732703                    ENDDO
    2874                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    2875                              surf_lsm_h%end_index(j,i)
     2704                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    28762705                       vmea(l)%measured_vars(m,n) = surf_lsm_h%us(mm)
    28772706                    ENDDO
    2878                     DO  mm = surf_usm_h%start_index(j,i),                      &
    2879                              surf_usm_h%end_index(j,i)
     2707                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    28802708                       vmea(l)%measured_vars(m,n) = surf_usm_h%us(mm)
    28812709                    ENDDO
     
    28852713                 DO  m = 1, vmea(l)%ns
    28862714!
    2887 !--                 Surface data is only available on inner subdomains, not
    2888 !--                 on ghost points. Hence, limit the indices.
     2715!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
     2716!-                  limit the indices.
    28892717                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    28902718                    j = MERGE( j           , nyn, j            < nyn )
     
    28922720                    i = MERGE( i           , nxr, i            < nxr )
    28932721
    2894                     DO  mm = surf_def_h(0)%start_index(j,i),                   &
    2895                              surf_def_h(0)%end_index(j,i)
     2722                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
    28962723                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%ts(mm)
    28972724                    ENDDO
    2898                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    2899                              surf_lsm_h%end_index(j,i)
     2725                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    29002726                       vmea(l)%measured_vars(m,n) = surf_lsm_h%ts(mm)
    29012727                    ENDDO
    2902                     DO  mm = surf_usm_h%start_index(j,i),                      &
    2903                              surf_usm_h%end_index(j,i)
     2728                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    29042729                       vmea(l)%measured_vars(m,n) = surf_usm_h%ts(mm)
    29052730                    ENDDO
     
    29092734                 DO  m = 1, vmea(l)%ns
    29102735!
    2911 !--                 Surface data is only available on inner subdomains, not
    2912 !--                 on ghost points. Hence, limit the indices.
     2736!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
     2737!--                 limit the indices.
    29132738                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    29142739                    j = MERGE( j           , nyn, j            < nyn )
     
    29162741                    i = MERGE( i           , nxr, i            < nxr )
    29172742
    2918                     DO  mm = surf_def_h(0)%start_index(j,i),                   &
    2919                              surf_def_h(0)%end_index(j,i)
     2743                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
    29202744                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%qsws(mm)
    29212745                    ENDDO
    2922                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    2923                              surf_lsm_h%end_index(j,i)
     2746                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    29242747                       vmea(l)%measured_vars(m,n) = surf_lsm_h%qsws(mm)
    29252748                    ENDDO
    2926                     DO  mm = surf_usm_h%start_index(j,i),                      &
    2927                              surf_usm_h%end_index(j,i)
     2749                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    29282750                       vmea(l)%measured_vars(m,n) = surf_usm_h%qsws(mm)
    29292751                    ENDDO
     
    29332755                 DO  m = 1, vmea(l)%ns
    29342756!
    2935 !--                 Surface data is only available on inner subdomains, not
    2936 !--                 on ghost points. Hence, limit the indices.
     2757!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
     2758!--                 limit the indices.
    29372759                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    29382760                    j = MERGE( j           , nyn, j            < nyn )
     
    29402762                    i = MERGE( i           , nxr, i            < nxr )
    29412763
    2942                     DO  mm = surf_def_h(0)%start_index(j,i),                   &
    2943                              surf_def_h(0)%end_index(j,i)
     2764                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
    29442765                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%shf(mm)
    29452766                    ENDDO
    2946                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    2947                              surf_lsm_h%end_index(j,i)
     2767                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    29482768                       vmea(l)%measured_vars(m,n) = surf_lsm_h%shf(mm)
    29492769                    ENDDO
    2950                     DO  mm = surf_usm_h%start_index(j,i),                      &
    2951                              surf_usm_h%end_index(j,i)
     2770                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    29522771                       vmea(l)%measured_vars(m,n) = surf_usm_h%shf(mm)
    29532772                    ENDDO
     
    29572776                 DO  m = 1, vmea(l)%ns
    29582777!
    2959 !--                 Surface data is only available on inner subdomains, not
    2960 !--                 on ghost points. Hence, limit the indices.
     2778!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
     2779!--                 limit the indices.
    29612780                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    29622781                    j = MERGE( j           , nyn, j            < nyn )
     
    29642783                    i = MERGE( i           , nxr, i            < nxr )
    29652784
    2966                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    2967                              surf_lsm_h%end_index(j,i)
     2785                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    29682786                       vmea(l)%measured_vars(m,n) = surf_lsm_h%ghf(mm)
    29692787                    ENDDO
     
    29732791!                  DO  m = 1, vmea(l)%ns
    29742792! !
    2975 ! !--                 Surface data is only available on inner subdomains, not
    2976 ! !--                 on ghost points. Hence, limit the indices.
     2793! !--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
     2794! !--                 limit the indices.
    29772795!                     j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    29782796!                     j = MERGE( j           , nyn, j            < nyn )
     
    29802798!                     i = MERGE( i           , nxr, i            < nxr )
    29812799!
    2982 !                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    2983 !                              surf_lsm_h%end_index(j,i)
     2800!                     DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    29842801!                        vmea(l)%measured_vars(m,n) = ?
    29852802!                     ENDDO
     
    29902807                    DO  m = 1, vmea(l)%ns
    29912808!
    2992 !--                    Surface data is only available on inner subdomains, not
    2993 !--                    on ghost points. Hence, limit the indices.
     2809!--                    Surface data is only available on inner subdomains, not on ghost points.
     2810!--                    Hence, limit the indices.
    29942811                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    29952812                       j = MERGE( j           , nyn, j            < nyn )
     
    29972814                       i = MERGE( i           , nxr, i            < nxr )
    29982815
    2999                        DO  mm = surf_lsm_h%start_index(j,i),                   &
    3000                                 surf_lsm_h%end_index(j,i)
     2816                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    30012817                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_net(mm)
    30022818                       ENDDO
    3003                        DO  mm = surf_usm_h%start_index(j,i),                   &
    3004                                 surf_usm_h%end_index(j,i)
     2819                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    30052820                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_net(mm)
    30062821                       ENDDO
     
    30122827                    DO  m = 1, vmea(l)%ns
    30132828!
    3014 !--                    Surface data is only available on inner subdomains, not
    3015 !--                    on ghost points. Hence, limit the indices.
     2829!--                    Surface data is only available on inner subdomains, not on ghost points.
     2830!--                    Hence, limit the indices.
    30162831                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    30172832                       j = MERGE( j           , nyn, j            < nyn )
     
    30192834                       i = MERGE( i           , nxr, i            < nxr )
    30202835
    3021                        DO  mm = surf_lsm_h%start_index(j,i),                   &
    3022                                 surf_lsm_h%end_index(j,i)
     2836                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    30232837                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_sw_out(mm)
    30242838                       ENDDO
    3025                        DO  mm = surf_usm_h%start_index(j,i),                   &
    3026                                 surf_usm_h%end_index(j,i)
     2839                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    30272840                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_sw_out(mm)
    30282841                       ENDDO
     
    30342847                    DO  m = 1, vmea(l)%ns
    30352848!
    3036 !--                    Surface data is only available on inner subdomains, not
    3037 !--                    on ghost points. Hence, limit the indices.
     2849!--                    Surface data is only available on inner subdomains, not on ghost points.
     2850!--                    Hence, limit the indices.
    30382851                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    30392852                       j = MERGE( j           , nyn, j            < nyn )
     
    30412854                       i = MERGE( i           , nxr, i            < nxr )
    30422855
    3043                        DO  mm = surf_lsm_h%start_index(j,i),                   &
    3044                                 surf_lsm_h%end_index(j,i)
     2856                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    30452857                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_sw_in(mm)
    30462858                       ENDDO
    3047                        DO  mm = surf_usm_h%start_index(j,i),                   &
    3048                                 surf_usm_h%end_index(j,i)
     2859                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    30492860                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_sw_in(mm)
    30502861                       ENDDO
     
    30562867                    DO  m = 1, vmea(l)%ns
    30572868!
    3058 !--                    Surface data is only available on inner subdomains, not
    3059 !--                    on ghost points. Hence, limit the indices.
     2869!--                    Surface data is only available on inner subdomains, not on ghost points.
     2870!--                    Hence, limit the indices.
    30602871                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    30612872                       j = MERGE( j           , nyn, j            < nyn )
     
    30632874                       i = MERGE( i           , nxr, i            < nxr )
    30642875
    3065                        DO  mm = surf_lsm_h%start_index(j,i),                   &
    3066                                 surf_lsm_h%end_index(j,i)
     2876                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    30672877                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_lw_out(mm)
    30682878                       ENDDO
    3069                        DO  mm = surf_usm_h%start_index(j,i),                   &
    3070                                 surf_usm_h%end_index(j,i)
     2879                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    30712880                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_lw_out(mm)
    30722881                       ENDDO
     
    30782887                    DO  m = 1, vmea(l)%ns
    30792888!
    3080 !--                    Surface data is only available on inner subdomains, not
    3081 !--                    on ghost points. Hence, limit the indices.
     2889!--                    Surface data is only available on inner subdomains, not on ghost points.
     2890!--                    Hence, limit the indices.
    30822891                       j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    30832892                       j = MERGE( j           , nyn, j            < nyn )
     
    30852894                       i = MERGE( i           , nxr, i            < nxr )
    30862895
    3087                        DO  mm = surf_lsm_h%start_index(j,i),                   &
    3088                                 surf_lsm_h%end_index(j,i)
     2896                       DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
    30892897                          vmea(l)%measured_vars(m,n) = surf_lsm_h%rad_lw_in(mm)
    30902898                       ENDDO
    3091                        DO  mm = surf_usm_h%start_index(j,i),                   &
    3092                                 surf_usm_h%end_index(j,i)
     2899                       DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
    30932900                          vmea(l)%measured_vars(m,n) = surf_usm_h%rad_lw_in(mm)
    30942901                       ENDDO
     
    31592966                          k = 0
    31602967!
    3161 !--                       Surface data is only available on inner subdomains,
    3162 !--                       not on ghost points. Hence, limit the indices.
     2968!--                       Surface data is only available on inner subdomains, not on ghost points.
     2969!--                       Hence, limit the indices.
    31632970                          j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    31642971                          j = MERGE( j           , nyn, j            < nyn )
     
    31963003                    k = vmea(l)%k_soil(m)
    31973004
    3198                     match_lsm = surf_lsm_h%start_index(j,i) <=                 &
    3199                                 surf_lsm_h%end_index(j,i)
    3200                     match_usm = surf_usm_h%start_index(j,i) <=                 &
    3201                                 surf_usm_h%end_index(j,i)
     3005                    match_lsm = surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i)
     3006                    match_usm = surf_usm_h%start_index(j,i) <= surf_usm_h%end_index(j,i)
    32023007
    32033008                    IF ( match_lsm )  THEN
     
    32203025                    k = vmea(l)%k_soil(m)
    32213026
    3222                     match_lsm = surf_lsm_h%start_index(j,i) <=                 &
    3223                                 surf_lsm_h%end_index(j,i)
     3027                    match_lsm = surf_lsm_h%start_index(j,i) <= surf_lsm_h%end_index(j,i)
    32243028
    32253029                    IF ( match_lsm )  THEN
     
    32313035
    32323036              CASE ( 'ts' ) ! surface temperature
     3037                 DO  m = 1, vmea(l)%ns
     3038!
     3039!--                 Surface data is only available on inner subdomains, not on ghost points. Hence,
     3040!--                 limit the indices.
     3041                    j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
     3042                    j = MERGE( j           , nyn, j            < nyn )
     3043                    i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
     3044                    i = MERGE( i           , nxr, i            < nxr )
     3045
     3046                    DO  mm = surf_def_h(0)%start_index(j,i), surf_def_h(0)%end_index(j,i)
     3047                       vmea(l)%measured_vars(m,n) = surf_def_h(0)%pt_surface(mm)
     3048                    ENDDO
     3049                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
     3050                       vmea(l)%measured_vars(m,n) = surf_lsm_h%pt_surface(mm)
     3051                    ENDDO
     3052                    DO  mm = surf_usm_h%start_index(j,i), surf_usm_h%end_index(j,i)
     3053                       vmea(l)%measured_vars(m,n) = surf_usm_h%pt_surface(mm)
     3054                    ENDDO
     3055                 ENDDO
     3056
     3057              CASE ( 'lwp' ) ! liquid water path
     3058                 IF ( ASSOCIATED( ql ) )  THEN
     3059                    DO  m = 1, vmea(l)%ns
     3060                       j = vmea(l)%j(m)
     3061                       i = vmea(l)%i(m)
     3062
     3063                       vmea(l)%measured_vars(m,n) = SUM( ql(nzb:nzt,j,i) * dzw(1:nzt+1) )          &
     3064                                                    * rho_surface
     3065                    ENDDO
     3066                 ENDIF
     3067
     3068              CASE ( 'ps' ) ! surface pressure
     3069                 vmea(l)%measured_vars(:,n) = surface_pressure
     3070
     3071              CASE ( 'pswrtg' ) ! platform speed above ground
     3072                 vmea(l)%measured_vars(:,n) = 0.0_wp
     3073
     3074              CASE ( 'pswrta' ) ! platform speed in air
     3075                 vmea(l)%measured_vars(:,n) = 0.0_wp
     3076
     3077              CASE ( 't_lw' ) ! water temperature
    32333078                 DO  m = 1, vmea(l)%ns
    32343079!
     
    32403085                    i = MERGE( i           , nxr, i            < nxr )
    32413086
    3242                     DO  mm = surf_def_h(0)%start_index(j,i),                   &
    3243                              surf_def_h(0)%end_index(j,i)
    3244                        vmea(l)%measured_vars(m,n) = surf_def_h(0)%pt_surface(mm)
    3245                     ENDDO
    3246                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    3247                              surf_lsm_h%end_index(j,i)
    3248                        vmea(l)%measured_vars(m,n) = surf_lsm_h%pt_surface(mm)
    3249                     ENDDO
    3250                     DO  mm = surf_usm_h%start_index(j,i),                      &
    3251                              surf_usm_h%end_index(j,i)
    3252                        vmea(l)%measured_vars(m,n) = surf_usm_h%pt_surface(mm)
    3253                     ENDDO
    3254                  ENDDO
    3255 
    3256               CASE ( 'lwp' ) ! liquid water path
    3257                  IF ( ASSOCIATED( ql ) )  THEN
    3258                     DO  m = 1, vmea(l)%ns
    3259                        j = vmea(l)%j(m)
    3260                        i = vmea(l)%i(m)
    3261 
    3262                        vmea(l)%measured_vars(m,n) = SUM( ql(nzb:nzt,j,i)       &
    3263                                                        * dzw(1:nzt+1) )        &
    3264                                                   * rho_surface
    3265                     ENDDO
    3266                  ENDIF
    3267 
    3268               CASE ( 'ps' ) ! surface pressure
    3269                  vmea(l)%measured_vars(:,n) = surface_pressure
    3270 
    3271               CASE ( 'pswrtg' ) ! platform speed above ground
    3272                  vmea(l)%measured_vars(:,n) = 0.0_wp
    3273 
    3274               CASE ( 'pswrta' ) ! platform speed in air
    3275                  vmea(l)%measured_vars(:,n) = 0.0_wp
    3276 
    3277               CASE ( 't_lw' ) ! water temperature
    3278                  DO  m = 1, vmea(l)%ns
    3279 !
    3280 !--                 Surface data is only available on inner subdomains, not
    3281 !--                 on ghost points. Hence, limit the indices.
    3282                     j = MERGE( vmea(l)%j(m), nys, vmea(l)%j(m) > nys )
    3283                     j = MERGE( j           , nyn, j            < nyn )
    3284                     i = MERGE( vmea(l)%i(m), nxl, vmea(l)%i(m) > nxl )
    3285                     i = MERGE( i           , nxr, i            < nxr )
    3286 
    3287                     DO  mm = surf_lsm_h%start_index(j,i),                      &
    3288                              surf_lsm_h%end_index(j,i)
    3289                        IF ( surf_lsm_h%water_surface(m) )                      &
    3290                           vmea(l)%measured_vars(m,n) = t_soil_h%var_2d(nzt,m)
     3087                    DO  mm = surf_lsm_h%start_index(j,i), surf_lsm_h%end_index(j,i)
     3088                       IF ( surf_lsm_h%water_surface(m) )                                          &
     3089                            vmea(l)%measured_vars(m,n) = t_soil_h%var_2d(nzt,m)
    32913090                    ENDDO
    32923091
     
    33073106     CALL cpu_log( log_point_s(27), 'VM sampling', 'stop' )
    33083107
    3309   END SUBROUTINE vm_sampling
     3108 END SUBROUTINE vm_sampling
    33103109
    33113110
Note: See TracChangeset for help on using the changeset viewer.