Changeset 4646


Ignore:
Timestamp:
Aug 24, 2020 4:02:40 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

Location:
palm/trunk/SOURCE
Files:
7 edited

Legend:

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

    r4370 r4646  
    11!> @file fft_xy_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/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4370 2020-01-10 14:00:44Z raasch
    2729! bugfix for Temperton-fft usage on GPU
    28 ! 
     30!
    2931! 4366 2020-01-09 08:12:43Z raasch
    3032! Vectorized Temperton-fft added
    31 ! 
     33!
    3234! 4360 2020-01-07 11:25:50Z suehring
    3335! Corrected "Former revisions" section
    34 ! 
     36!
    3537! 4069 2019-07-01 14:05:51Z Giersch
    3638! Code added to avoid compiler warnings
    37 ! 
     39!
    3840! 3655 2019-01-07 16:51:22Z knoop
    3941! OpenACC port for SPEC
     
    5052!------------------------------------------------------------------------------!
    5153 MODULE fft_xy
    52  
    53 
    54     USE control_parameters,                                                    &
     54
     55
     56    USE control_parameters,                                                                        &
    5557        ONLY:  fft_method, loop_optimization, message_string
    56        
     58
    5759    USE cuda_fft_interfaces
    58        
    59     USE indices,                                                               &
     60
     61    USE indices,                                                                                   &
    6062        ONLY:  nx, ny, nz
    6163
     
    6769
    6870    USE kinds
    69    
    70     USE singleton,                                                             &
     71
     72    USE singleton,                                                                                 &
    7173        ONLY: fftn
    72    
     74
    7375    USE temperton_fft
    74    
    75     USE transpose_indices,                                                     &
     76
     77    USE transpose_indices,                                                                         &
    7678        ONLY:  nxl_y, nxr_y, nyn_x, nys_x, nzb_x, nzb_y, nzt_x, nzt_y
    7779
     
    7981
    8082    PRIVATE
    81     PUBLIC fft_x, fft_x_1d, fft_y, fft_y_1d, fft_init, fft_x_m, fft_y_m, f_vec_x, temperton_fft_vec
     83    PUBLIC fft_init, f_vec_x, fft_x, fft_x_1d, fft_x_m, fft_y, fft_y_1d, fft_y_m, temperton_fft_vec
    8284
    8385    INTEGER(iwp), DIMENSION(:), ALLOCATABLE, SAVE ::  ifax_x  !<
     
    9193    REAL(wp), SAVE ::  sqr_dnx  !<
    9294    REAL(wp), SAVE ::  sqr_dny  !<
    93    
    94     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trigs_x  !< 
     95
     96    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trigs_x  !<
    9597    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trigs_y  !<
    9698
     
    98100
    99101#if defined( __ibm )
    100     INTEGER(iwp), PARAMETER ::  nau1 = 20000  !< 
     102    INTEGER(iwp), PARAMETER ::  nau1 = 20000  !<
    101103    INTEGER(iwp), PARAMETER ::  nau2 = 22000  !<
    102104!
    103 !-- The following working arrays contain tables and have to be "save" and
    104 !-- shared in OpenMP sense
    105     REAL(wp), DIMENSION(nau1), SAVE ::  aux1  !<
     105!-- The following working arrays contain tables and have to be "save" and shared in OpenMP sense
     106    REAL(wp), DIMENSION(nau1), SAVE ::  aux1  !<
    106107    REAL(wp), DIMENSION(nau1), SAVE ::  auy1  !<
    107     REAL(wp), DIMENSION(nau1), SAVE ::  aux3  !< 
     108    REAL(wp), DIMENSION(nau1), SAVE ::  aux3  !<
    108109    REAL(wp), DIMENSION(nau1), SAVE ::  auy3  !<
    109    
     110
    110111#elif defined( __nec_fft )
    111112    INTEGER(iwp), SAVE ::  nz1  !<
    112    
     113
    113114    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_xb  !<
    114     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_xf  !< 
     115    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_xf  !<
    115116    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_yb  !<
    116117    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  trig_yf  !<
    117    
     118
    118119#elif defined( __cuda_fft )
    119120    INTEGER(C_INT), SAVE ::  plan_xf  !<
     
    126127#if defined( __fftw )
    127128    INCLUDE  'fftw3.f03'
     129    COMPLEX(KIND=C_DOUBLE_COMPLEX), DIMENSION(:), ALLOCATABLE, SAVE ::  x_out  !<
     130    COMPLEX(KIND=C_DOUBLE_COMPLEX), DIMENSION(:), ALLOCATABLE, SAVE ::  y_out  !<
     131
    128132    INTEGER(KIND=C_INT) ::  nx_c  !<
    129133    INTEGER(KIND=C_INT) ::  ny_c  !<
    130    
    131     COMPLEX(KIND=C_DOUBLE_COMPLEX), DIMENSION(:), ALLOCATABLE, SAVE ::  x_out  !<
    132     COMPLEX(KIND=C_DOUBLE_COMPLEX), DIMENSION(:), ALLOCATABLE, SAVE ::         &
    133        y_out  !<
    134    
    135     REAL(KIND=C_DOUBLE), DIMENSION(:), ALLOCATABLE, SAVE ::                    &
    136        x_in   !<
    137     REAL(KIND=C_DOUBLE), DIMENSION(:), ALLOCATABLE, SAVE ::                    &
    138        y_in   !<
     134
     135    REAL(KIND=C_DOUBLE), DIMENSION(:), ALLOCATABLE, SAVE ::  x_in   !<
     136    REAL(KIND=C_DOUBLE), DIMENSION(:), ALLOCATABLE, SAVE ::  y_in   !<
    139137    !$OMP THREADPRIVATE( x_out, y_out, x_in, y_in )
    140    
    141    
     138
     139
    142140    TYPE(C_PTR), SAVE ::  plan_xf, plan_xi, plan_yf, plan_yi
    143141#endif
     
    176174
    177175
    178 !------------------------------------------------------------------------------!
     176!--------------------------------------------------------------------------------------------------!
    179177! Description:
    180178! ------------
    181179!> @todo Missing subroutine description.
    182 !------------------------------------------------------------------------------!
     180!--------------------------------------------------------------------------------------------------!
    183181    SUBROUTINE fft_init
    184182
     
    192190!--    in OpenMP sense
    193191#if defined( __ibm )
     192       REAL(wp), DIMENSION(nau2)   ::  aux2   !<
     193       REAL(wp), DIMENSION(nau2)   ::  auy2   !<
     194       REAL(wp), DIMENSION(nau2)   ::  aux4   !<
     195       REAL(wp), DIMENSION(nau2)   ::  auy4   !<
    194196       REAL(wp), DIMENSION(0:nx+2) ::  workx  !<
    195197       REAL(wp), DIMENSION(0:ny+2) ::  worky  !<
    196        REAL(wp), DIMENSION(nau2)   ::  aux2   !<
    197        REAL(wp), DIMENSION(nau2)   ::  auy2   !<
    198        REAL(wp), DIMENSION(nau2)   ::  aux4   !<
    199        REAL(wp), DIMENSION(nau2)   ::  auy4   !<
    200198#elif defined( __nec_fft )
    201199       REAL(wp), DIMENSION(0:nx+3,nz+1)   ::  work_x  !<
     
    203201       REAL(wp), DIMENSION(6*(nx+3),nz+1) ::  workx   !<
    204202       REAL(wp), DIMENSION(6*(ny+3),nz+1) ::  worky   !<
    205 #endif 
     203#endif
    206204
    207205!
     
    233231!
    234232!--       Initialize tables for fft along x
    235           CALL DRCFT( 1, workx, 1, workx, 1, nx+1, 1,  1, sqr_dnx, aux1, nau1, &
    236                       aux2, nau2 )
    237           CALL DCRFT( 1, workx, 1, workx, 1, nx+1, 1, -1, sqr_dnx, aux3, nau1, &
    238                       aux4, nau2 )
     233          CALL DRCFT( 1, workx, 1, workx, 1, nx+1, 1,  1, sqr_dnx, aux1, nau1, aux2, nau2 )
     234          CALL DCRFT( 1, workx, 1, workx, 1, nx+1, 1, -1, sqr_dnx, aux3, nau1, aux4, nau2 )
    239235!
    240236!--       Initialize tables for fft along y
    241           CALL DRCFT( 1, worky, 1, worky, 1, ny+1, 1,  1, sqr_dny, auy1, nau1, &
    242                       auy2, nau2 )
    243           CALL DCRFT( 1, worky, 1, worky, 1, ny+1, 1, -1, sqr_dny, auy3, nau1, &
    244                       auy4, nau2 )
     237          CALL DRCFT( 1, worky, 1, worky, 1, ny+1, 1,  1, sqr_dny, auy1, nau1, auy2, nau2 )
     238          CALL DCRFT( 1, worky, 1, worky, 1, ny+1, 1, -1, sqr_dny, auy3, nau1, auy4, nau2 )
    245239#elif defined( __nec_fft )
    246           message_string = 'fft method "' // TRIM( fft_method) // &
    247                            '" currently does not work on NEC'
     240          message_string = 'fft method "' // TRIM( fft_method) // '" currently does not work on NEC'
    248241          CALL message( 'fft_init', 'PA0187', 1, 2, 0, 6, 0 )
    249242
    250           ALLOCATE( trig_xb(2*(nx+1)), trig_xf(2*(nx+1)),                      &
    251                     trig_yb(2*(ny+1)), trig_yf(2*(ny+1)) )
     243          ALLOCATE( trig_xb(2*(nx+1)), trig_xf(2*(nx+1)), trig_yb(2*(ny+1)), trig_yf(2*(ny+1)) )
    252244
    253245          work_x = 0.0_wp
     
    260252          CALL DZFFT( 0, nx+1, sqr_dnx, work_x, work_x, trig_xf, workx, 0 )
    261253          CALL ZDFFT( 0, nx+1, sqr_dnx, work_x, work_x, trig_xb, workx, 0 )
    262           CALL DZFFTM( 0, nx+1, nz1, sqr_dnx, work_x, nx+4, work_x, nx+4,      &
    263                        trig_xf, workx, 0 )
    264           CALL ZDFFTM( 0, nx+1, nz1, sqr_dnx, work_x, nx+4, work_x, nx+4,      &
    265                        trig_xb, workx, 0 )
     254          CALL DZFFTM( 0, nx+1, nz1, sqr_dnx, work_x, nx+4, work_x, nx+4, trig_xf, workx, 0 )
     255          CALL ZDFFTM( 0, nx+1, nz1, sqr_dnx, work_x, nx+4, work_x, nx+4, trig_xb, workx, 0 )
    266256!
    267257!--       Initialize tables for fft along y (non-vector and vector case (M))
    268258          CALL DZFFT( 0, ny+1, sqr_dny, work_y, work_y, trig_yf, worky, 0 )
    269259          CALL ZDFFT( 0, ny+1, sqr_dny, work_y, work_y, trig_yb, worky, 0 )
    270           CALL DZFFTM( 0, ny+1, nz1, sqr_dny, work_y, ny+4, work_y, ny+4,      &
    271                        trig_yf, worky, 0 )
    272           CALL ZDFFTM( 0, ny+1, nz1, sqr_dny, work_y, ny+4, work_y, ny+4,      &
    273                        trig_yb, worky, 0 )
     260          CALL DZFFTM( 0, ny+1, nz1, sqr_dny, work_y, ny+4, work_y, ny+4, trig_yf, worky, 0 )
     261          CALL ZDFFTM( 0, ny+1, nz1, sqr_dny, work_y, ny+4, work_y, ny+4, trig_yb, worky, 0 )
    274262#elif defined( __cuda_fft )
    275263          CALL CUFFTPLAN1D( plan_xf, nx+1, CUFFT_D2Z, (nyn_x-nys_x+1) * (nzt_x-nzb_x+1) )
     
    303291          ny_c = ny+1
    304292          !$OMP PARALLEL
    305           ALLOCATE( x_in(0:nx+2), y_in(0:ny+2), x_out(0:(nx+1)/2),             &
    306                     y_out(0:(ny+1)/2) )
     293          ALLOCATE( x_in(0:nx+2), y_in(0:ny+2), x_out(0:(nx+1)/2), y_out(0:(ny+1)/2) )
    307294          !$OMP END PARALLEL
    308295          plan_xf = FFTW_PLAN_DFT_R2C_1D( nx_c, x_in, x_out, FFTW_ESTIMATE )
     
    321308       ELSE
    322309
    323           message_string = 'fft method "' // TRIM( fft_method) // &
    324                            '" not available'
     310          message_string = 'fft method "' // TRIM( fft_method) // '" not available'
    325311          CALL message( 'fft_init', 'PA0189', 1, 2, 0, 6, 0 )
    326312       ENDIF
     
    329315
    330316
    331 !------------------------------------------------------------------------------!
     317!--------------------------------------------------------------------------------------------------!
    332318! Description:
    333319! ------------
    334 !> Fourier-transformation along x-direction.                 
     320!> Fourier-transformation along x-direction.
    335321!> Version for 2D-decomposition.
    336 !> It uses internal algorithms (Singleton or Temperton) or      
    337 !> system-specific routines, if they are available           
    338 !------------------------------------------------------------------------------!
    339  
     322!> It uses internal algorithms (Singleton or Temperton) or system-specific routines, if they are
     323!> available.
     324!--------------------------------------------------------------------------------------------------!
     325
    340326    SUBROUTINE fft_x( ar, direction, ar_2d, ar_inv )
    341327
     
    344330
    345331       CHARACTER (LEN=*) ::  direction  !<
    346        
     332
    347333       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
    348334
    349        INTEGER(iwp) ::  i          !< 
     335       INTEGER(iwp) ::  i          !<
    350336       INTEGER(iwp) ::  ishape(1)  !<
    351337       INTEGER(iwp) ::  j          !<
     
    354340
    355341       LOGICAL ::  forward_fft !<
    356        
     342
    357343       REAL(wp), DIMENSION(0:nx+2) ::  work   !<
    358344       REAL(wp), DIMENSION(nx+2)   ::  work1  !<
    359        
     345
    360346       REAL(wp), DIMENSION(:,:), ALLOCATABLE           ::  work_vec  !<
    361347       REAL(wp), DIMENSION(0:nx,nys_x:nyn_x), OPTIONAL ::  ar_2d     !<
    362348
     349       REAL(wp), DIMENSION(0:nx,nys_x:nyn_x,nzb_x:nzt_x)           ::  ar       !<
    363350       REAL(wp), DIMENSION(nys_x:nyn_x,nzb_x:nzt_x,0:nx), OPTIONAL ::  ar_inv   !<
    364        REAL(wp), DIMENSION(0:nx,nys_x:nyn_x,nzb_x:nzt_x)           ::  ar       !<
    365351
    366352#if defined( __ibm )
    367        REAL(wp), DIMENSION(nau2) ::  aux2  !< 
     353       REAL(wp), DIMENSION(nau2) ::  aux2  !<
    368354       REAL(wp), DIMENSION(nau2) ::  aux4  !<
    369355#elif defined( __nec_fft )
     
    387373
    388374!
    389 !--       Performing the fft with singleton's software works on every system,
    390 !--       since it is part of the model
     375!--       Performing the fft with singleton's software works on every system, since it is part of
     376!--       the model.
    391377          ALLOCATE( cwork(0:nx) )
    392      
    393           IF ( forward_fft )   then
     378
     379          IF ( forward_fft )  THEN
    394380
    395381             !$OMP PARALLEL PRIVATE ( cwork, i, ishape, j, k )
     
    425411                   cwork(0) = CMPLX( ar(0,j,k), 0.0_wp, KIND=wp )
    426412                   DO  i = 1, (nx+1)/2 - 1
    427                       cwork(i)      = CMPLX( ar(i,j,k), -ar(nx+1-i,j,k),       &
    428                                              KIND=wp )
    429                       cwork(nx+1-i) = CMPLX( ar(i,j,k),  ar(nx+1-i,j,k),       &
    430                                              KIND=wp )
     413                      cwork(i)      = CMPLX( ar(i,j,k), -ar(nx+1-i,j,k), KIND=wp )
     414                      cwork(nx+1-i) = CMPLX( ar(i,j,k),  ar(nx+1-i,j,k), KIND=wp )
    431415                   ENDDO
    432416                   cwork((nx+1)/2) = CMPLX( ar((nx+1)/2,j,k), 0.0_wp, KIND=wp )
     
    450434
    451435!
    452 !--       Performing the fft with Temperton's software works on every system,
    453 !--       since it is part of the model
     436!--       Performing the fft with Temperton's software works on every system, since it is part of
     437!--       the model.
    454438          IF ( forward_fft )  THEN
    455439
     
    633617                      x_out(0) = CMPLX( ar_2d(0,j), 0.0_wp, KIND=wp )
    634618                      DO  i = 1, (nx+1)/2 - 1
    635                          x_out(i) = CMPLX( ar_2d(i,j), ar_2d(nx+1-i,j),        &
    636                                            KIND=wp )
    637                       ENDDO
    638                       x_out((nx+1)/2) = CMPLX( ar_2d((nx+1)/2,j), 0.0_wp,      &
    639                                                KIND=wp )
     619                         x_out(i) = CMPLX( ar_2d(i,j), ar_2d(nx+1-i,j), KIND=wp )
     620                      ENDDO
     621                      x_out((nx+1)/2) = CMPLX( ar_2d((nx+1)/2,j), 0.0_wp, KIND=wp )
    640622
    641623                   ELSE
     
    645627                         x_out(i) = CMPLX( ar(i,j,k), ar(nx+1-i,j,k), KIND=wp )
    646628                      ENDDO
    647                       x_out((nx+1)/2) = CMPLX( ar((nx+1)/2,j,k), 0.0_wp,       &
    648                                                KIND=wp )
     629                      x_out((nx+1)/2) = CMPLX( ar((nx+1)/2,j,k), 0.0_wp, KIND=wp )
    649630
    650631                   ENDIF
     
    670651                DO  j = nys_x, nyn_x
    671652
    672                    CALL DRCFT( 0, ar, 1, work, 1, nx+1, 1, 1, sqr_dnx, aux1,   &
    673                                nau1, aux2, nau2 )
     653                   CALL DRCFT( 0, ar, 1, work, 1, nx+1, 1, 1, sqr_dnx, aux1, nau1, aux2, nau2 )
    674654
    675655                   DO  i = 0, (nx+1)/2
     
    700680                   work(nx+2) = 0.0_wp
    701681
    702                    CALL DCRFT( 0, work, 1, work, 1, nx+1, 1, -1, sqr_dnx,      &
    703                                aux3, nau1, aux4, nau2 )
     682                   CALL DCRFT( 0, work, 1, work, 1, nx+1, 1, -1, sqr_dnx, aux3, nau1, aux4, nau2 )
    704683
    705684                   DO  i = 0, nx
     
    725704
    726705                   CALL DZFFT( 1, nx+1, sqr_dnx, work, work, trig_xf, work2, 0 )
    727      
     706
    728707                   DO  i = 0, (nx+1)/2
    729708                      ar(i,j,k) = work(2*i)
     
    797776
    798777                   DO  i = 1, (nx+1)/2 - 1
    799                       ar_tmp(i,j,k) = CMPLX( ar(i,j,k), ar(nx+1-i,j,k),        &
    800                                              KIND=wp )
    801                    ENDDO
    802                    ar_tmp((nx+1)/2,j,k) = CMPLX( ar((nx+1)/2,j,k), 0.0_wp,     &
    803                                                  KIND=wp )
     778                      ar_tmp(i,j,k) = CMPLX( ar(i,j,k), ar(nx+1-i,j,k), KIND=wp )
     779                   ENDDO
     780                   ar_tmp((nx+1)/2,j,k) = CMPLX( ar((nx+1)/2,j,k), 0.0_wp, KIND=wp )
    804781
    805782                ENDDO
     
    818795    END SUBROUTINE fft_x
    819796
    820 !------------------------------------------------------------------------------!
     797!--------------------------------------------------------------------------------------------------!
    821798! Description:
    822799! ------------
    823800!> Fourier-transformation along x-direction.
    824801!> Version for 1D-decomposition.
    825 !> It uses internal algorithms (Singleton or Temperton) or
    826 !> system-specific routines, if they are available
    827 !------------------------------------------------------------------------------!
    828  
     802!> It uses internal algorithms (Singleton or Temperton) or system-specific routines, if they are
     803!> available.
     804!--------------------------------------------------------------------------------------------------!
     805
    829806    SUBROUTINE fft_x_1d( ar, direction )
    830807
     
    833810
    834811       CHARACTER (LEN=*) ::  direction  !<
    835        
     812
    836813       INTEGER(iwp) ::  i               !<
    837814       INTEGER(iwp) ::  ishape(1)       !<
     
    842819       REAL(wp), DIMENSION(0:nx+2) ::  work   !<
    843820       REAL(wp), DIMENSION(nx+2)   ::  work1  !<
    844        
     821
    845822       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
    846        
     823
    847824#if defined( __ibm )
    848825       REAL(wp), DIMENSION(nau2) ::  aux2       !<
     
    861838
    862839!
    863 !--       Performing the fft with singleton's software works on every system,
    864 !--       since it is part of the model
     840!--       Performing the fft with singleton's software works on every system, since it is part of
     841!--       the model.
    865842          ALLOCATE( cwork(0:nx) )
    866      
    867           IF ( forward_fft )   then
     843
     844          IF ( forward_fft )  THEN
    868845
    869846             DO  i = 0, nx
     
    902879
    903880!
    904 !--       Performing the fft with Temperton's software works on every system,
    905 !--       since it is part of the model
     881!--       Performing the fft with Temperton's software works on every system, since it is part of
     882!--       the model.
    906883          IF ( forward_fft )  THEN
    907884
     
    966943          IF ( forward_fft )  THEN
    967944
    968              CALL DRCFT( 0, ar, 1, work, 1, nx+1, 1, 1, sqr_dnx, aux1, nau1,   &
    969                          aux2, nau2 )
     945             CALL DRCFT( 0, ar, 1, work, 1, nx+1, 1, 1, sqr_dnx, aux1, nau1, aux2, nau2 )
    970946
    971947             DO  i = 0, (nx+1)/2
     
    987963             work(nx+2) = 0.0_wp
    988964
    989              CALL DCRFT( 0, work, 1, work, 1, nx+1, 1, -1, sqr_dnx, aux3, nau1, &
    990                          aux4, nau2 )
     965             CALL DCRFT( 0, work, 1, work, 1, nx+1, 1, -1, sqr_dnx, aux3, nau1, aux4, nau2 )
    991966
    992967             DO  i = 0, nx
     
    1001976
    1002977             CALL DZFFT( 1, nx+1, sqr_dnx, work, work, trig_xf, work2, 0 )
    1003      
     978
    1004979             DO  i = 0, (nx+1)/2
    1005980                ar(i) = work(2*i)
     
    10311006    END SUBROUTINE fft_x_1d
    10321007
    1033 !------------------------------------------------------------------------------!
     1008!--------------------------------------------------------------------------------------------------!
    10341009! Description:
    10351010! ------------
    10361011!> Fourier-transformation along y-direction.
    10371012!> Version for 2D-decomposition.
    1038 !> It uses internal algorithms (Singleton or Temperton) or
    1039 !> system-specific routines, if they are available.
    1040 !> 
     1013!> It uses internal algorithms (Singleton or Temperton) or system-specific routines, if they are
     1014!> available.
     1015!>
    10411016!> direction:  'forward' or 'backward'
    1042 !> ar, ar_tr:  3D data arrays 
     1017!> ar, ar_tr:  3D data arrays
    10431018!>             forward:   ar: before  ar_tr: after transformation
    10441019!>             backward:  ar_tr: before  ar: after transfosition
    1045 !> 
     1020!>
    10461021!> In case of non-overlapping transposition/transformation:
    1047 !> nxl_y_bound = nxl_y_l = nxl_y 
    1048 !> nxr_y_bound = nxr_y_l = nxr_y 
    1049 !> 
     1022!> nxl_y_bound = nxl_y_l = nxl_y
     1023!> nxr_y_bound = nxr_y_l = nxr_y
     1024!>
    10501025!> In case of overlapping transposition/transformation
    1051 !> - nxl_y_bound  and  nxr_y_bound have the original values of
    1052 !>   nxl_y, nxr_y.  ar_tr is dimensioned using these values.
    1053 !> - nxl_y_l = nxr_y_r.  ar is dimensioned with these values, so that
    1054 !>   transformation is carried out for a 2D-plane only.
    1055 !------------------------------------------------------------------------------!
    1056  
    1057     SUBROUTINE fft_y( ar, direction, ar_tr, nxl_y_bound, nxr_y_bound, nxl_y_l, &
    1058                       nxr_y_l, ar_inv )
     1026!> - nxl_y_bound  and  nxr_y_bound have the original values of nxl_y, nxr_y.  ar_tr is dimensioned
     1027!>   using these values.
     1028!> - nxl_y_l = nxr_y_r.  ar is dimensioned with these values, so that transformation is carried out
     1029!>   for a 2D-plane only.
     1030!--------------------------------------------------------------------------------------------------!
     1031
     1032    SUBROUTINE fft_y( ar, direction, ar_tr, nxl_y_bound, nxr_y_bound, nxl_y_l, nxr_y_l, ar_inv )
    10591033
    10601034
     
    10621036
    10631037       CHARACTER (LEN=*) ::  direction  !<
    1064        
     1038
    10651039       INTEGER(iwp) ::  i            !<
    1066        INTEGER(iwp) ::  j            !< 
     1040       INTEGER(iwp) ::  j            !<
    10671041       INTEGER(iwp) ::  jshape(1)    !<
    10681042       INTEGER(iwp) ::  k            !<
     
    10771051       REAL(wp), DIMENSION(0:ny+2) ::  work   !<
    10781052       REAL(wp), DIMENSION(ny+2)   ::  work1  !<
    1079        
     1053
    10801054       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  f_vec_y
    10811055       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  work_vec
     
    10861060
    10871061       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
    1088        
     1062
    10891063#if defined( __ibm )
    10901064       REAL(wp), DIMENSION(nau2) ::  auy2  !<
     
    10931067       REAL(wp), DIMENSION(6*(ny+1)) ::  work2  !<
    10941068#elif defined( __cuda_fft )
    1095        COMPLEX(dp), DIMENSION(0:(ny+1)/2,nxl_y:nxr_y,nzb_y:nzt_y) ::           &
    1096           ar_tmp  !<
     1069       COMPLEX(dp), DIMENSION(0:(ny+1)/2,nxl_y:nxr_y,nzb_y:nzt_y) ::  ar_tmp  !<
    10971070       !$ACC DECLARE CREATE(ar_tmp)
    10981071#endif
     
    11081081
    11091082!
    1110 !--       Performing the fft with singleton's software works on every system,
    1111 !--       since it is part of the model
     1083!--       Performing the fft with singleton's software works on every system, since it is part of
     1084!--       the model.
    11121085          ALLOCATE( cwork(0:ny) )
    11131086
    1114           IF ( forward_fft )   then
     1087          IF ( forward_fft )  THEN
    11151088
    11161089             !$OMP PARALLEL PRIVATE ( cwork, i, jshape, j, k )
     
    11461119                   cwork(0) = CMPLX( ar_tr(0,i,k), 0.0_wp, KIND=wp )
    11471120                   DO  j = 1, (ny+1)/2 - 1
    1148                       cwork(j)      = CMPLX( ar_tr(j,i,k), -ar_tr(ny+1-j,i,k), &
    1149                                              KIND=wp )
    1150                       cwork(ny+1-j) = CMPLX( ar_tr(j,i,k),  ar_tr(ny+1-j,i,k), &
    1151                                              KIND=wp )
    1152                    ENDDO
    1153                    cwork((ny+1)/2) = CMPLX( ar_tr((ny+1)/2,i,k), 0.0_wp,       &
    1154                                             KIND=wp )
     1121                      cwork(j)      = CMPLX( ar_tr(j,i,k), -ar_tr(ny+1-j,i,k), KIND=wp )
     1122                      cwork(ny+1-j) = CMPLX( ar_tr(j,i,k),  ar_tr(ny+1-j,i,k), KIND=wp )
     1123                   ENDDO
     1124                   cwork((ny+1)/2) = CMPLX( ar_tr((ny+1)/2,i,k), 0.0_wp, KIND=wp )
    11551125
    11561126                   jshape = SHAPE( cwork )
     
    11721142
    11731143!
    1174 !--       Performing the fft with Temperton's software works on every system,
    1175 !--       since it is part of the model
     1144!--       Performing the fft with Temperton's software works on every system, since it is part of
     1145!--       the model.
    11761146          IF ( forward_fft )  THEN
    11771147
     
    13611331                   y_out(0) = CMPLX( ar_tr(0,i,k), 0.0_wp, KIND=wp )
    13621332                   DO  j = 1, (ny+1)/2 - 1
    1363                       y_out(j) = CMPLX( ar_tr(j,i,k), ar_tr(ny+1-j,i,k),       &
    1364                                         KIND=wp )
    1365                    ENDDO
    1366                    y_out((ny+1)/2) = CMPLX( ar_tr((ny+1)/2,i,k), 0.0_wp,       &
    1367                                             KIND=wp )
     1333                      y_out(j) = CMPLX( ar_tr(j,i,k), ar_tr(ny+1-j,i,k), KIND=wp )
     1334                   ENDDO
     1335                   y_out((ny+1)/2) = CMPLX( ar_tr((ny+1)/2,i,k), 0.0_wp, KIND=wp )
    13681336
    13691337                   CALL FFTW_EXECUTE_DFT_C2R( plan_yi, y_out, y_in )
     
    13871355                DO  i = nxl_y_l, nxr_y_l
    13881356
    1389                    CALL DRCFT( 0, ar, 1, work, 1, ny+1, 1, 1, sqr_dny, auy1,   &
    1390                                nau1, auy2, nau2 )
     1357                   CALL DRCFT( 0, ar, 1, work, 1, ny+1, 1, 1, sqr_dny, auy1, nau1, auy2, nau2 )
    13911358
    13921359                   DO  j = 0, (ny+1)/2
     
    14171384                   work(ny+2) = 0.0_wp
    14181385
    1419                    CALL DCRFT( 0, work, 1, work, 1, ny+1, 1, -1, sqr_dny,      &
    1420                                auy3, nau1, auy4, nau2 )
     1386                   CALL DCRFT( 0, work, 1, work, 1, ny+1, 1, -1, sqr_dny, auy3, nau1, auy4, nau2 )
    14211387
    14221388                   DO  j = 0, ny
     
    14911457
    14921458                   DO  j = 0, (ny+1)/2
    1493                       ar(j,i,k)      = REAL( ar_tmp(j,i,k), KIND=wp )  * dny
     1459                      ar(j,i,k)      = REAL( ar_tmp(j,i,k), KIND=wp ) * dny
    14941460                   ENDDO
    14951461
     
    15111477
    15121478                   DO  j = 1, (ny+1)/2 - 1
    1513                       ar_tmp(j,i,k) = CMPLX( ar(j,i,k), ar(ny+1-j,i,k),        &
    1514                                              KIND=wp )
    1515                    ENDDO
    1516                    ar_tmp((ny+1)/2,i,k) = CMPLX( ar((ny+1)/2,i,k), 0.0_wp,     &
    1517                                                  KIND=wp )
     1479                      ar_tmp(j,i,k) = CMPLX( ar(j,i,k), ar(ny+1-j,i,k), KIND=wp )
     1480                   ENDDO
     1481                   ar_tmp((ny+1)/2,i,k) = CMPLX( ar((ny+1)/2,i,k), 0.0_wp, KIND=wp )
    15181482
    15191483                ENDDO
     
    15321496    END SUBROUTINE fft_y
    15331497
    1534 !------------------------------------------------------------------------------!
     1498!--------------------------------------------------------------------------------------------------!
    15351499! Description:
    15361500! ------------
    15371501!> Fourier-transformation along y-direction.
    15381502!> Version for 1D-decomposition.
    1539 !> It uses internal algorithms (Singleton or Temperton) or
    1540 !> system-specific routines, if they are available.
    1541 !------------------------------------------------------------------------------!
    1542  
     1503!> It uses internal algorithms (Singleton or Temperton) or system-specific routines, if they are
     1504!> available.
     1505!--------------------------------------------------------------------------------------------------!
     1506
    15431507    SUBROUTINE fft_y_1d( ar, direction )
    15441508
     
    15471511
    15481512       CHARACTER (LEN=*) ::  direction
    1549        
     1513
    15501514       INTEGER(iwp) ::  j          !<
    15511515       INTEGER(iwp) ::  jshape(1)  !<
     
    15561520       REAL(wp), DIMENSION(0:ny+2)  ::  work   !<
    15571521       REAL(wp), DIMENSION(ny+2)    ::  work1  !<
    1558        
     1522
    15591523       COMPLEX(wp), DIMENSION(:), ALLOCATABLE ::  cwork  !<
    1560        
     1524
    15611525#if defined( __ibm )
    15621526       REAL(wp), DIMENSION(nau2) ::  auy2  !<
     
    15751539
    15761540!
    1577 !--       Performing the fft with singleton's software works on every system,
    1578 !--       since it is part of the model
     1541!--       Performing the fft with singleton's software works on every system, since it is part of
     1542!--       the model.
    15791543          ALLOCATE( cwork(0:ny) )
    15801544
     
    16181582
    16191583!
    1620 !--       Performing the fft with Temperton's software works on every system,
    1621 !--       since it is part of the model
     1584!--       Performing the fft with Temperton's software works on every system, since it is part of
     1585!--       the model.
    16221586          IF ( forward_fft )  THEN
    16231587
     
    16821646          IF ( forward_fft )  THEN
    16831647
    1684              CALL DRCFT( 0, ar, 1, work, 1, ny+1, 1, 1, sqr_dny, auy1, nau1,   &
    1685                          auy2, nau2 )
     1648             CALL DRCFT( 0, ar, 1, work, 1, ny+1, 1, 1, sqr_dny, auy1, nau1, auy2, nau2 )
    16861649
    16871650             DO  j = 0, (ny+1)/2
     
    17031666             work(ny+2) = 0.0_wp
    17041667
    1705              CALL DCRFT( 0, work, 1, work, 1, ny+1, 1, -1, sqr_dny, auy3,      &
    1706                          nau1, auy4, nau2 )
     1668             CALL DCRFT( 0, work, 1, work, 1, ny+1, 1, -1, sqr_dny, auy3, nau1, auy4, nau2 )
    17071669
    17081670             DO  j = 0, ny
     
    17471709    END SUBROUTINE fft_y_1d
    17481710
    1749 !------------------------------------------------------------------------------!
     1711!--------------------------------------------------------------------------------------------------!
    17501712! Description:
    17511713! ------------
    17521714!> Fourier-transformation along x-direction.
    1753 !> Version for 1d domain decomposition
     1715!> Version for 1d domain decomposition,
    17541716!> using multiple 1D FFT from Math Keisan on NEC or Temperton-algorithm
    1755 !> (no singleton-algorithm on NEC because it does not vectorize)
    1756 !------------------------------------------------------------------------------!
    1757  
     1717!> (no singleton-algorithm on NEC because it does not vectorize).
     1718!--------------------------------------------------------------------------------------------------!
     1719
    17581720    SUBROUTINE fft_x_m( ar, direction )
    17591721
     
    17621724
    17631725       CHARACTER (LEN=*) ::  direction  !<
    1764        
     1726
    17651727       INTEGER(iwp) ::  i     !<
    17661728       INTEGER(iwp) ::  k     !<
     
    17731735       REAL(wp), DIMENSION(0:nx+3,nz+1)   ::  ai     !<
    17741736       REAL(wp), DIMENSION(6*(nx+4),nz+1) ::  work1  !<
    1775        
     1737
    17761738#if defined( __nec_fft )
    17771739       COMPLEX(wp), DIMENSION(:,:), ALLOCATABLE ::  work
     
    18271789
    18281790!
    1829 !--          Tables are initialized once more. This call should not be
    1830 !--          necessary, but otherwise program aborts in asymmetric case
    1831              CALL DZFFTM( 0, nx+1, nz1, sqr_dnx, work, nx+4, work, nx+4,       &
    1832                           trig_xf, work1, 0 )
     1791!--          Tables are initialized once more. This call should not be necessary, but otherwise
     1792!--          program aborts in asymmetric case.
     1793             CALL DZFFTM( 0, nx+1, nz1, sqr_dnx, work, nx+4, work, nx+4, trig_xf, work1, 0 )
    18331794
    18341795             ai(0:nx,1:nz) = ar(0:nx,1:nz)
     
    18371798             ENDIF
    18381799
    1839              CALL DZFFTM( 1, nx+1, nz1, sqr_dnx, ai, siza, work, sizw,         &
    1840                           trig_xf, work1, 0 )
     1800             CALL DZFFTM( 1, nx+1, nz1, sqr_dnx, ai, siza, work, sizw, trig_xf, work1, 0 )
    18411801
    18421802             DO  k = 1, nz
     
    18541814!--          Tables are initialized once more. This call should not be
    18551815!--          necessary, but otherwise program aborts in asymmetric case
    1856              CALL ZDFFTM( 0, nx+1, nz1, sqr_dnx, work, nx+4, work, nx+4,       &
    1857                           trig_xb, work1, 0 )
     1816             CALL ZDFFTM( 0, nx+1, nz1, sqr_dnx, work, nx+4, work, nx+4, trig_xb, work1, 0 )
    18581817
    18591818             IF ( nz1 > nz )  THEN
     
    18681827             ENDDO
    18691828
    1870              CALL ZDFFTM( -1, nx+1, nz1, sqr_dnx, work, sizw, ai, siza, &
    1871                           trig_xb, work1, 0 )
     1829             CALL ZDFFTM( -1, nx+1, nz1, sqr_dnx, work, sizw, ai, siza, trig_xb, work1, 0 )
    18721830
    18731831             ar(0:nx,1:nz) = ai(0:nx,1:nz)
     
    18821840    END SUBROUTINE fft_x_m
    18831841
    1884 !------------------------------------------------------------------------------!
     1842!--------------------------------------------------------------------------------------------------!
    18851843! Description:
    18861844! ------------
    18871845!> Fourier-transformation along y-direction.
    1888 !> Version for 1d domain decomposition
     1846!> Version for 1d domain decomposition,
    18891847!> using multiple 1D FFT from Math Keisan on NEC or Temperton-algorithm
    1890 !> (no singleton-algorithm on NEC because it does not vectorize)
    1891 !------------------------------------------------------------------------------!
    1892  
     1848!> (no singleton-algorithm on NEC because it does not vectorize).
     1849!--------------------------------------------------------------------------------------------------!
     1850
    18931851    SUBROUTINE fft_y_m( ar, ny1, direction )
    18941852
     
    18971855
    18981856       CHARACTER (LEN=*) ::  direction  !<
    1899        
    1900        INTEGER(iwp) ::  j     !< 
     1857
     1858       INTEGER(iwp) ::  j     !<
    19011859       INTEGER(iwp) ::  k     !<
    19021860       INTEGER(iwp) ::  ny1   !<
     
    19641922
    19651923!
    1966 !--          Tables are initialized once more. This call should not be
    1967 !--          necessary, but otherwise program aborts in asymmetric case
    1968              CALL DZFFTM( 0, ny+1, nz1, sqr_dny, work, ny+4, work, ny+4, &
    1969                           trig_yf, work1, 0 )
     1924!--          Tables are initialized once more. This call should not be necessary, but otherwise
     1925!--          program aborts in asymmetric case.
     1926             CALL DZFFTM( 0, ny+1, nz1, sqr_dny, work, ny+4, work, ny+4, trig_yf, work1, 0 )
    19701927
    19711928             ai(0:ny,1:nz) = ar(0:ny,1:nz)
     
    19741931             ENDIF
    19751932
    1976              CALL DZFFTM( 1, ny+1, nz1, sqr_dny, ai, siza, work, sizw, &
    1977                           trig_yf, work1, 0 )
     1933             CALL DZFFTM( 1, ny+1, nz1, sqr_dny, ai, siza, work, sizw, trig_yf, work1, 0 )
    19781934
    19791935             DO  k = 1, nz
     
    19891945
    19901946!
    1991 !--          Tables are initialized once more. This call should not be
    1992 !--          necessary, but otherwise program aborts in asymmetric case
    1993              CALL ZDFFTM( 0, ny+1, nz1, sqr_dny, work, ny+4, work, ny+4, &
    1994                           trig_yb, work1, 0 )
     1947!--          Tables are initialized once more. This call should not be necessary, but otherwise
     1948!--          program aborts in asymmetric case.
     1949             CALL ZDFFTM( 0, ny+1, nz1, sqr_dny, work, ny+4, work, ny+4, trig_yb, work1, 0 )
    19951950
    19961951             IF ( nz1 > nz )  THEN
     
    20051960             ENDDO
    20061961
    2007              CALL ZDFFTM( -1, ny+1, nz1, sqr_dny, work, sizw, ai, siza, &
    2008                           trig_yb, work1, 0 )
     1962             CALL ZDFFTM( -1, ny+1, nz1, sqr_dny, work, sizw, ai, siza, trig_yb, work1, 0 )
    20091963
    20101964             ar(0:ny,1:nz) = ai(0:ny,1:nz)
  • palm/trunk/SOURCE/flow_statistics.f90

    r4581 r4646  
    11!> @file flow_statistics.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/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! ------------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4581 2020-06-29 08:49:58Z suehring
    2729! Formatting adjustment
    28 ! 
     30!
    2931! 4551 2020-06-02 10:22:25Z suehring
    3032! Bugfix in summation for statistical regions
    31 ! 
     33!
    3234! 4521 2020-05-06 11:39:49Z schwenkel
    3335! Rename variable
    34 ! 
     36!
    3537! 4502 2020-04-17 16:14:16Z schwenkel
    3638! Implementation of ice microphysics
    37 ! 
     39!
    3840! 4472 2020-03-24 12:21:00Z Giersch
    3941! Calculations of the Kolmogorov lengt scale eta implemented
     
    4345!
    4446! 4463 2020-03-17 09:27:36Z Giersch
    45 ! Calculate horizontally averaged profiles of all velocity components at the
    46 ! same place
     47! Calculate horizontally averaged profiles of all velocity components at the same place
    4748!
    4849! 4444 2020-03-05 15:59:50Z raasch
     
    5051!
    5152! 4442 2020-03-04 19:21:13Z suehring
    52 ! Change order of dimension in surface array %frac to allow for better
    53 ! vectorization.
     53! Change order of dimension in surface array %frac to allow for better vectorization.
    5454!
    5555! 4441 2020-03-04 19:20:35Z suehring
    56 ! Introduction of wall_flags_total_0, which currently sets bits based on static
    57 ! topography information used in wall_flags_static_0
     56! Introduction of wall_flags_total_0, which currently sets bits based on static topography
     57! information used in wall_flags_static_0
    5858!
    5959! 4329 2019-12-10 15:46:36Z motisi
     
    6767!
    6868! 4039 2019-06-18 10:32:41Z suehring
    69 ! Correct conversion to kinematic scalar fluxes in case of pw-scheme and
    70 ! statistic regions
     69! Correct conversion to kinematic scalar fluxes in case of pw-scheme and statistic regions
    7170!
    7271! 3828 2019-03-27 19:36:23Z raasch
     
    8281! Description:
    8382! ------------
    84 !> Compute average profiles and further average flow quantities for the different
    85 !> user-defined (sub-)regions. The region indexed 0 is the total model domain.
     83!> Compute average profiles and further average flow quantities for the different user-defined
     84!> (sub-)regions. The region indexed 0 is the total model domain.
    8685!>
    87 !> @note For simplicity, nzb_s_inner and nzb_diff_s_inner are being used as a
    88 !>       lower vertical index for k-loops for all variables, although strictly
    89 !>       speaking the k-loops would have to be split up according to the staggered
    90 !>       grid. However, this implies no error since staggered velocity components
    91 !>       are zero at the walls and inside buildings.
    92 !------------------------------------------------------------------------------!
     86!> @note For simplicity, nzb_s_inner and nzb_diff_s_inner are used as a lower vertical index for
     87!>       k-loops for all variables, although strictly speaking the k-loops would have to be split
     88!>       up according to the staggered grid. However, this implies no error since staggered velocity
     89!>       components are zero at the walls and inside buildings.
     90!--------------------------------------------------------------------------------------------------!
    9391 SUBROUTINE flow_statistics
    9492
    9593
    96     USE arrays_3d,                                                             &
    97         ONLY:  ddzu, ddzw, e, heatflux_output_conversion, hyp, km, kh,         &
    98                momentumflux_output_conversion, nc, ni, nr, p, prho, prr, pt, q,&
    99                qc, qi, ql, qr, rho_air, rho_air_zw, rho_ocean, s,              &
    100                sa, u, ug, v, vg, vpt, w, w_subs, waterflux_output_conversion,  &
    101                zw, d_exner
    102 
    103     USE basic_constants_and_equations_mod,                                     &
     94    USE arrays_3d,                                                                                 &
     95        ONLY:  ddzu, ddzw, d_exner, e, heatflux_output_conversion, hyp, km, kh,                    &
     96               momentumflux_output_conversion, nc, ni, nr, p, prho, prr, pt, q, qc, qi, ql, qr,    &
     97               rho_air, rho_air_zw, rho_ocean, s, sa, u, ug, v, vg, vpt, w, w_subs,                &
     98               waterflux_output_conversion, zw
     99
     100    USE basic_constants_and_equations_mod,                                                         &
    104101        ONLY:  g, lv_d_cp
    105102
    106     USE bulk_cloud_model_mod,                                                  &
    107         ONLY: bulk_cloud_model, microphysics_morrison, microphysics_seifert,   &
    108               microphysics_ice_phase
    109 
    110     USE chem_modules,                                                          &
     103    USE bulk_cloud_model_mod,                                                                      &
     104        ONLY: bulk_cloud_model, microphysics_morrison, microphysics_seifert, microphysics_ice_phase
     105
     106    USE chem_modules,                                                                              &
    111107        ONLY:  max_pr_cs
    112108
    113     USE control_parameters,                                                    &
    114         ONLY:   air_chemistry, average_count_pr, cloud_droplets, do_sum,       &
    115                 dt_3d, humidity, initializing_actions, kolmogorov_length_scale,&
    116                 land_surface, large_scale_forcing, large_scale_subsidence,     &
    117                 max_pr_user, message_string, neutral, ocean_mode,              &
    118                 passive_scalar, simulated_time, simulated_time_at_begin,       &
    119                 use_subsidence_tendencies, use_surface_fluxes, use_top_fluxes, &
    120                 ws_scheme_mom, ws_scheme_sca, salsa, max_pr_salsa
    121 
    122     USE cpulog,                                                                &
     109    USE control_parameters,                                                                        &
     110        ONLY:   air_chemistry, average_count_pr, cloud_droplets, do_sum, dt_3d, humidity,          &
     111                initializing_actions, kolmogorov_length_scale, land_surface, large_scale_forcing,  &
     112                large_scale_subsidence, max_pr_salsa, max_pr_user, message_string, neutral,        &
     113                ocean_mode, passive_scalar, salsa, simulated_time, simulated_time_at_begin,        &
     114                use_subsidence_tendencies, use_surface_fluxes, use_top_fluxes, ws_scheme_mom,      &
     115                ws_scheme_sca
     116
     117    USE cpulog,                                                                                    &
    123118        ONLY:   cpu_log, log_point
    124119
    125     USE grid_variables,                                                        &
     120    USE grid_variables,                                                                            &
    126121        ONLY:   ddx, ddy
    127122
    128     USE indices,                                                               &
    129         ONLY:   ngp_2dh, ngp_2dh_s_inner, ngp_3d, ngp_3d_inner, nxl, nxr, nyn, &
    130                 nys, nzb, nzt, topo_min_level, wall_flags_total_0
     123    USE indices,                                                                                   &
     124        ONLY:   ngp_2dh, ngp_2dh_s_inner, ngp_3d, ngp_3d_inner, nxl, nxr, nyn, nys, nzb, nzt,      &
     125                topo_min_level, wall_flags_total_0
    131126
    132127#if defined( __parallel )
    133     USE indices,                                                               &
     128    USE indices,                                                                                   &
    134129        ONLY:  ngp_sums, ngp_sums_ls
    135130#endif
     
    137132    USE kinds
    138133
    139     USE land_surface_model_mod,                                                &
     134    USE land_surface_model_mod,                                                                    &
    140135        ONLY:   m_soil_h, nzb_soil, nzt_soil, t_soil_h
    141136
    142     USE lsf_nudging_mod,                                                       &
     137    USE lsf_nudging_mod,                                                                           &
    143138        ONLY:   td_lsa_lpt, td_lsa_q, td_sub_lpt, td_sub_q, time_vert
    144139
    145     USE module_interface,                                                      &
     140    USE module_interface,                                                                          &
    146141        ONLY:  module_interface_statistics
    147142
    148     USE netcdf_interface,                                                      &
     143    USE netcdf_interface,                                                                          &
    149144        ONLY:  dots_rad, dots_soil, dots_max
    150145
    151146    USE pegrid
    152147
    153     USE radiation_model_mod,                                                   &
    154         ONLY:  radiation, radiation_scheme,                                    &
    155                rad_lw_in, rad_lw_out, rad_lw_cs_hr, rad_lw_hr,                 &
     148    USE radiation_model_mod,                                                                       &
     149        ONLY:  radiation, radiation_scheme,                                                        &
     150               rad_lw_in, rad_lw_out, rad_lw_cs_hr, rad_lw_hr,                                     &
    156151               rad_sw_in, rad_sw_out, rad_sw_cs_hr, rad_sw_hr
    157152
    158153    USE statistics
    159154
    160     USE surface_mod,                                                           &
     155    USE surface_mod,                                                                               &
    161156        ONLY :  surf_def_h, surf_lsm_h, surf_usm_h
    162157
     
    215210    REAL(wp) ::  sums_ll(nzb:nzt+1,2)  !<
    216211
     212
    217213    CALL cpu_log( log_point(10), 'flow_statistics', 'start' )
    218214
    219215
    220216!
    221 !-- To be on the safe side, check whether flow_statistics has already been
    222 !-- called once after the current time step
     217!-- To be on the safe side, check whether flow_statistics has already been called once after the
     218!-- current time step.
    223219    IF ( flow_statistics_called )  THEN
    224220
    225        message_string = 'flow_statistics is called two times within one ' // &
    226                         'timestep'
     221       message_string = 'flow_statistics is called two times within one ' // 'timestep'
    227222       CALL message( 'flow_statistics', 'PA0190', 1, 2, 0, 6, 0 )
    228223
     
    243238
    244239!
    245 !--    Store sums that have been computed in other subroutines in summation
    246 !--    array
     240!--    Store sums that have been computed in other subroutines in summation array
    247241       sums_l(:,11,:) = sums_l_l(:,sr,:)      ! mixing length from diffusivities
    248242!--    WARNING: next line still has to be adjusted for OpenMP
    249        sums_l(:,21,0) = sums_wsts_bc_l(:,sr) *                                 &
     243       sums_l(:,21,0) = sums_wsts_bc_l(:,sr) *                                                     &
    250244                        heatflux_output_conversion  ! heat flux from advec_s_bc
    251245       sums_l(nzb+9,pr_palm,0)  = sums_divold_l(sr)  ! old divergence from pres
     
    253247
    254248!
    255 !--    When calcuating horizontally-averaged total (resolved- plus subgrid-
    256 !--    scale) vertical fluxes and velocity variances by using commonly-
    257 !--    applied Reynolds-based methods ( e.g. <w'pt'> = (w-<w>)*(pt-<pt>) )
    258 !--    in combination with the 5th order advection scheme, pronounced
    259 !--    artificial kinks could be observed in the vertical profiles near the
    260 !--    surface. Please note: these kinks were not related to the model truth,
    261 !--    i.e. these kinks are just related to an evaluation problem.
    262 !--    In order avoid these kinks, vertical fluxes and horizontal as well
    263 !--    vertical velocity variances are calculated directly within the advection
    264 !--    routines, according to the numerical discretization, to evaluate the
    265 !--    statistical quantities as they will appear within the prognostic
    266 !--    equations.
    267 !--    Copy the turbulent quantities, evaluated in the advection routines to
    268 !--    the local array sums_l() for further computations.
     249!--    When calcuating horizontally-averaged total (resolved- plus subgrid-scale) vertical fluxes
     250!--    and velocity variances by using commonly-applied Reynolds-based methods
     251!--    ( e.g. <w'pt'> = (w-<w>)*(pt-<pt>) ) in combination with the 5th order advection scheme,
     252!--    pronounced artificial kinks could be observed in the vertical profiles near the surface.
     253!--    Please note: these kinks were not related to the model truth, i.e. these kinks are just
     254!--    related to an evaluation problem.
     255!--    In order avoid these kinks, vertical fluxes and horizontal as well vertical velocity
     256!--    variances are calculated directly within the advection routines, according to the numerical
     257!--    discretization, to evaluate the statistical quantities as they will appear within the
     258!--    prognostic equations.
     259!--    Copy the turbulent quantities, evaluated in the advection routines to the local array
     260!--    sums_l() for further computations.
    269261       IF ( ws_scheme_mom .AND. sr == 0 )  THEN
    270262
    271263!
    272 !--       According to the Neumann bc for the horizontal velocity components,
    273 !--       the corresponding fluxes has to satisfiy the same bc.
     264!--       According to the Neumann bc for the horizontal velocity components, the corresponding
     265!--       fluxes has to satisfiy the same bc.
    274266          IF ( ocean_mode )  THEN
    275267             sums_us2_ws_l(nzt+1,:) = sums_us2_ws_l(nzt,:)
     
    280272!
    281273!--          Swap the turbulent quantities evaluated in advec_ws.
    282              sums_l(:,13,i) = sums_wsus_ws_l(:,i)                              &
    283                               * momentumflux_output_conversion ! w*u*
    284              sums_l(:,15,i) = sums_wsvs_ws_l(:,i)                              &
    285                               * momentumflux_output_conversion ! w*v*
    286              sums_l(:,30,i) = sums_us2_ws_l(:,i)        ! u*2
    287              sums_l(:,31,i) = sums_vs2_ws_l(:,i)        ! v*2
    288              sums_l(:,32,i) = sums_ws2_ws_l(:,i)        ! w*2
    289              sums_l(:,34,i) = sums_l(:,34,i) + 0.5_wp *                        &
    290                               ( sums_us2_ws_l(:,i) + sums_vs2_ws_l(:,i) +      &
    291                                 sums_ws2_ws_l(:,i) )    ! e*
     274             sums_l(:,13,i) = sums_wsus_ws_l(:,i) * momentumflux_output_conversion ! w*u*
     275             sums_l(:,15,i) = sums_wsvs_ws_l(:,i) * momentumflux_output_conversion ! w*v*
     276             sums_l(:,30,i) = sums_us2_ws_l(:,i)                                   ! u*2
     277             sums_l(:,31,i) = sums_vs2_ws_l(:,i)                                   ! v*2
     278             sums_l(:,32,i) = sums_ws2_ws_l(:,i)                                   ! w*2
     279             sums_l(:,34,i) = sums_l(:,34,i) + 0.5_wp *                                            &
     280                              ( sums_us2_ws_l(:,i) + sums_vs2_ws_l(:,i) + sums_ws2_ws_l(:,i) )  ! e*
    292281          ENDDO
    293282
     
    297286
    298287          DO  i = 0, threads_per_task-1
    299              sums_l(:,17,i)                        = sums_wspts_ws_l(:,i)      &
    300                                            * heatflux_output_conversion  ! w*pt*
    301              IF ( ocean_mode     ) sums_l(:,66,i)  = sums_wssas_ws_l(:,i) ! w*sa*
    302              IF ( humidity       ) sums_l(:,49,i)  = sums_wsqs_ws_l(:,i)       &
    303                                            * waterflux_output_conversion  ! w*q*
    304              IF ( passive_scalar ) sums_l(:,114,i) = sums_wsss_ws_l(:,i)  ! w*s*
     288             sums_l(:,17,i)                        = sums_wspts_ws_l(:,i)                          &
     289                                                     * heatflux_output_conversion   ! w*pt*
     290             IF ( ocean_mode     ) sums_l(:,66,i)  = sums_wssas_ws_l(:,i)           ! w*sa*
     291             IF ( humidity       ) sums_l(:,49,i)  = sums_wsqs_ws_l(:,i)                           &
     292                                                     * waterflux_output_conversion  ! w*q*
     293             IF ( passive_scalar ) sums_l(:,114,i) = sums_wsss_ws_l(:,i)            ! w*s*
    305294          ENDDO
    306295
     
    308297!
    309298!--    Horizontally averaged profiles of horizontal velocities and temperature.
    310 !--    They must have been computed before, because they are already required
    311 !--    for other horizontal averages.
     299!--    They must have been computed before, because they are already required for other horizontal
     300!--    averages.
    312301       tn = 0
    313302       !$OMP PARALLEL PRIVATE( i, j, k, tn, flag )
     
    321310                flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 22 ) )
    322311                !$ACC ATOMIC
    323                 sums_l(k,1,tn)  = sums_l(k,1,tn)  + u(k,j,i)  * rmask(j,i,sr)  &
    324                                                               * flag
    325                 !$ACC ATOMIC
    326                 sums_l(k,2,tn)  = sums_l(k,2,tn)  + v(k,j,i)  * rmask(j,i,sr)  &
    327                                                               * flag
    328                 !$ACC ATOMIC
    329                 sums_l(k,4,tn)  = sums_l(k,4,tn)  + pt(k,j,i) * rmask(j,i,sr)  &
    330                                                               * flag
     312                sums_l(k,1,tn)  = sums_l(k,1,tn)  + u(k,j,i)  * rmask(j,i,sr) * flag
     313                !$ACC ATOMIC
     314                sums_l(k,2,tn)  = sums_l(k,2,tn)  + v(k,j,i)  * rmask(j,i,sr) * flag
     315                !$ACC ATOMIC
     316                sums_l(k,4,tn)  = sums_l(k,4,tn)  + pt(k,j,i) * rmask(j,i,sr) * flag
    331317             ENDDO
    332318          ENDDO
     
    341327             DO  j =  nys, nyn
    342328                DO  k = nzb, nzt+1
    343                    sums_l(k,23,tn)  = sums_l(k,23,tn) + sa(k,j,i)              &
    344                                     * rmask(j,i,sr)                            &
    345                                     * MERGE( 1.0_wp, 0.0_wp,                   &
    346                                              BTEST( wall_flags_total_0(k,j,i), 22 ) )
     329                   sums_l(k,23,tn)  = sums_l(k,23,tn) + sa(k,j,i)                                  &
     330                                      * rmask(j,i,sr)                                              &
     331                                      * MERGE( 1.0_wp, 0.0_wp,                                     &
     332                                               BTEST( wall_flags_total_0(k,j,i), 22 ) )
    347333                ENDDO
    348334             ENDDO
     
    351337
    352338!
    353 !--    Horizontally averaged profiles of virtual potential temperature,
    354 !--    total water content, water vapor mixing ratio and liquid water potential
    355 !--    temperature
     339!--    Horizontally averaged profiles of virtual potential temperature, total water content, water
     340!--    vapor mixing ratio and liquid water potential temperature
    356341       IF ( humidity )  THEN
    357342          !$OMP DO
     
    360345                DO  k = nzb, nzt+1
    361346                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 22 ) )
    362                    sums_l(k,44,tn)  = sums_l(k,44,tn) +                        &
    363                                       vpt(k,j,i) * rmask(j,i,sr) * flag
    364                    sums_l(k,41,tn)  = sums_l(k,41,tn) +                        &
    365                                       q(k,j,i) * rmask(j,i,sr)   * flag
     347                   sums_l(k,44,tn)  = sums_l(k,44,tn) + vpt(k,j,i) * rmask(j,i,sr) * flag
     348                   sums_l(k,41,tn)  = sums_l(k,41,tn) + q(k,j,i) * rmask(j,i,sr)   * flag
    366349                ENDDO
    367350             ENDDO
     
    374357                      flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 22 ) )
    375358                      sums_l(k,42,tn) = sums_l(k,42,tn) +                      &
    376                                       ( q(k,j,i) - ql(k,j,i) ) * rmask(j,i,sr) &
    377                                                                * flag
    378                       sums_l(k,43,tn) = sums_l(k,43,tn) + (                    &
    379                                       pt(k,j,i) + lv_d_cp * d_exner(k) * ql(k,j,i) &
    380                                                           ) * rmask(j,i,sr)    &
    381                                                             * flag
     359                                        ( q(k,j,i) - ql(k,j,i) ) * rmask(j,i,sr) * flag
     360                      sums_l(k,43,tn) = sums_l(k,43,tn) + (                                        &
     361                                           pt(k,j,i) + lv_d_cp * d_exner(k) * ql(k,j,i)            &
     362                                                          ) * rmask(j,i,sr) * flag
    382363                   ENDDO
    383364                ENDDO
     
    393374             DO  j =  nys, nyn
    394375                DO  k = nzb, nzt+1
    395                    sums_l(k,115,tn)  = sums_l(k,115,tn) + s(k,j,i)             &
    396                                     * rmask(j,i,sr)                            &
    397                                     * MERGE( 1.0_wp, 0.0_wp,                   &
    398                                              BTEST( wall_flags_total_0(k,j,i), 22 ) )
     376                   sums_l(k,115,tn)  = sums_l(k,115,tn) + s(k,j,i)                                 &
     377                                       * rmask(j,i,sr)                                             &
     378                                       * MERGE( 1.0_wp, 0.0_wp,                                    &
     379                                                BTEST( wall_flags_total_0(k,j,i), 22 ) )
    399380                ENDDO
    400381             ENDDO
     
    430411!--    Compute total sum from local sums
    431412       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    432        CALL MPI_ALLREDUCE( sums_l(nzb,1,0), sums(nzb,1), nzt+2-nzb, MPI_REAL, &
    433                            MPI_SUM, comm2d, ierr )
     413       CALL MPI_ALLREDUCE( sums_l(nzb,1,0), sums(nzb,1), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,    &
     414                           ierr )
    434415       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    435        CALL MPI_ALLREDUCE( sums_l(nzb,2,0), sums(nzb,2), nzt+2-nzb, MPI_REAL, &
    436                            MPI_SUM, comm2d, ierr )
     416       CALL MPI_ALLREDUCE( sums_l(nzb,2,0), sums(nzb,2), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,    &
     417                           ierr )
    437418       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    438        CALL MPI_ALLREDUCE( sums_l(nzb,4,0), sums(nzb,4), nzt+2-nzb, MPI_REAL, &
    439                            MPI_SUM, comm2d, ierr )
     419       CALL MPI_ALLREDUCE( sums_l(nzb,4,0), sums(nzb,4), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,    &
     420                           ierr )
    440421       IF ( ocean_mode )  THEN
    441422          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    442           CALL MPI_ALLREDUCE( sums_l(nzb,23,0), sums(nzb,23), nzt+2-nzb,       &
    443                               MPI_REAL, MPI_SUM, comm2d, ierr )
     423          CALL MPI_ALLREDUCE( sums_l(nzb,23,0), sums(nzb,23), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,&
     424                              ierr )
    444425       ENDIF
    445426       IF ( humidity ) THEN
    446427          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    447           CALL MPI_ALLREDUCE( sums_l(nzb,44,0), sums(nzb,44), nzt+2-nzb,       &
    448                               MPI_REAL, MPI_SUM, comm2d, ierr )
     428          CALL MPI_ALLREDUCE( sums_l(nzb,44,0), sums(nzb,44), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,&
     429                              ierr )
    449430          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    450           CALL MPI_ALLREDUCE( sums_l(nzb,41,0), sums(nzb,41), nzt+2-nzb,       &
    451                               MPI_REAL, MPI_SUM, comm2d, ierr )
     431          CALL MPI_ALLREDUCE( sums_l(nzb,41,0), sums(nzb,41), nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d,&
     432                              ierr )
    452433          IF ( bulk_cloud_model ) THEN
    453434             IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    454              CALL MPI_ALLREDUCE( sums_l(nzb,42,0), sums(nzb,42), nzt+2-nzb,    &
    455                                  MPI_REAL, MPI_SUM, comm2d, ierr )
     435             CALL MPI_ALLREDUCE( sums_l(nzb,42,0), sums(nzb,42), nzt+2-nzb, MPI_REAL, MPI_SUM,     &
     436                                 comm2d, ierr )
    456437             IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    457              CALL MPI_ALLREDUCE( sums_l(nzb,43,0), sums(nzb,43), nzt+2-nzb,    &
    458                                  MPI_REAL, MPI_SUM, comm2d, ierr )
     438             CALL MPI_ALLREDUCE( sums_l(nzb,43,0), sums(nzb,43), nzt+2-nzb, MPI_REAL, MPI_SUM,     &
     439                                 comm2d, ierr )
    459440          ENDIF
    460441       ENDIF
     
    462443       IF ( passive_scalar )  THEN
    463444          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    464           CALL MPI_ALLREDUCE( sums_l(nzb,115,0), sums(nzb,115), nzt+2-nzb,       &
    465                               MPI_REAL, MPI_SUM, comm2d, ierr )
     445          CALL MPI_ALLREDUCE( sums_l(nzb,115,0), sums(nzb,115), nzt+2-nzb, MPI_REAL, MPI_SUM,      &
     446                              comm2d, ierr )
    466447       ENDIF
    467448#else
     
    482463
    483464!
    484 !--    Final values are obtained by division by the total number of grid points
    485 !--    used for summation. After that store profiles.
     465!--    Final values are obtained by division by the total number of grid points used for summation.
     466!--    After that store profiles.
    486467       sums(:,1) = sums(:,1) / ngp_2dh(sr)
    487468       sums(:,2) = sums(:,2) / ngp_2dh(sr)
     
    517498!
    518499!--    Passive scalar
    519        IF ( passive_scalar )  hom(:,1,115,sr) = sums(:,115) /                  &
    520             ngp_2dh_s_inner(:,sr)                    ! s
    521 
    522 !
    523 !--    Horizontally averaged profiles of the remaining prognostic variables,
    524 !--    variances, the total and the perturbation energy (single values in last
    525 !--    column of sums_l) and some diagnostic quantities.
    526 !--    NOTE: for simplicity, nzb_s_inner is used below, although strictly
    527 !--    ----  speaking the following k-loop would have to be split up and
    528 !--          rearranged according to the staggered grid.
    529 !--          However, this implies no error since staggered velocity components
    530 !--          are zero at the walls and inside buildings.
     500       IF ( passive_scalar )  hom(:,1,115,sr) = sums(:,115) / ngp_2dh_s_inner(:,sr)  ! s
     501
     502!
     503!--    Horizontally averaged profiles of the remaining prognostic variables, variances, the total
     504!--    and the perturbation energy (single values in last column of sums_l) and some diagnostic
     505!--    quantities.
     506!--    NOTE: for simplicity, nzb_s_inner is used below, although strictly speaking the following
     507!--    ----  k-loop would have to be split up and rearranged according to the staggered grid.
     508!--          However, this implies no error since staggered velocity components are zero at the
     509!--          walls and inside buildings.
    531510       tn = 0
    532511       !$OMP PARALLEL PRIVATE( i, j, k, pts, sums_ll,                          &
     
    554533!--             Prognostic and diagnostic variables
    555534                !$ACC ATOMIC
    556                 sums_l(k,3,tn)  = sums_l(k,3,tn)  + w(k,j,i)  * rmask(j,i,sr)  &
    557                                                               * flag
    558                 !$ACC ATOMIC
    559                 sums_l(k,8,tn)  = sums_l(k,8,tn)  + e(k,j,i)  * rmask(j,i,sr)  &
    560                                                               * flag
    561                 !$ACC ATOMIC
    562                 sums_l(k,9,tn)  = sums_l(k,9,tn)  + km(k,j,i) * rmask(j,i,sr)  &
    563                                                               * flag
    564                 !$ACC ATOMIC
    565                 sums_l(k,10,tn) = sums_l(k,10,tn) + kh(k,j,i) * rmask(j,i,sr)  &
    566                                                               * flag
    567                 !$ACC ATOMIC
    568                 sums_l(k,40,tn) = sums_l(k,40,tn) + ( p(k,j,i)                 &
    569                                          / momentumflux_output_conversion(k) ) &
    570                                                               * flag
     535                sums_l(k,3,tn)  = sums_l(k,3,tn)  + w(k,j,i)  * rmask(j,i,sr) * flag
     536                !$ACC ATOMIC
     537                sums_l(k,8,tn)  = sums_l(k,8,tn)  + e(k,j,i)  * rmask(j,i,sr) * flag
     538                !$ACC ATOMIC
     539                sums_l(k,9,tn)  = sums_l(k,9,tn)  + km(k,j,i) * rmask(j,i,sr) * flag
     540                !$ACC ATOMIC
     541                sums_l(k,10,tn) = sums_l(k,10,tn) + kh(k,j,i) * rmask(j,i,sr) * flag
     542                !$ACC ATOMIC
     543                sums_l(k,40,tn) = sums_l(k,40,tn) + ( p(k,j,i)                                     &
     544                                         / momentumflux_output_conversion(k) ) * flag
    571545
    572546                !$ACC ATOMIC
    573547                sums_l(k,33,tn) = sums_l(k,33,tn) + &
    574                                   ( pt(k,j,i)-hom(k,1,4,sr) )**2 * rmask(j,i,sr)&
    575                                                                  * flag
     548                                  ( pt(k,j,i)-hom(k,1,4,sr) )**2 * rmask(j,i,sr) * flag
    576549#ifndef _OPENACC
    577550                IF ( humidity )  THEN
    578                    sums_l(k,70,tn) = sums_l(k,70,tn) + &
    579                                   ( q(k,j,i)-hom(k,1,41,sr) )**2 * rmask(j,i,sr)&
    580                                                                  * flag
     551                   sums_l(k,70,tn) = sums_l(k,70,tn) +                                             &
     552                                     ( q(k,j,i)-hom(k,1,41,sr) )**2 * rmask(j,i,sr) * flag
    581553                ENDIF
    582554                IF ( passive_scalar )  THEN
    583                    sums_l(k,116,tn) = sums_l(k,116,tn) + &
    584                                   ( s(k,j,i)-hom(k,1,115,sr) )**2 * rmask(j,i,sr)&
    585                                                                   * flag
     555                   sums_l(k,116,tn) = sums_l(k,116,tn) +                                           &
     556                                      ( s(k,j,i)-hom(k,1,115,sr) )**2 * rmask(j,i,sr) * flag
    586557                ENDIF
    587558#endif
     
    590561!--             (Computation of the skewness of w further below)
    591562                !$ACC ATOMIC
    592                 sums_l(k,38,tn) = sums_l(k,38,tn) + w(k,j,i)**3 * rmask(j,i,sr) &
    593                                                                 * flag
    594 
    595                 sums_l_etot  = sums_l_etot + &
    596                                         0.5_wp * ( u(k,j,i)**2 + v(k,j,i)**2 +  &
    597                                         w(k,j,i)**2 )            * rmask(j,i,sr)&
    598                                                                  * flag
    599 
    600 !
    601 !--             Computation of the Kolmogorov length scale. Calculation is based
    602 !--             on gradients of the deviations from the horizontal mean.
     563                sums_l(k,38,tn) = sums_l(k,38,tn) + w(k,j,i)**3 * rmask(j,i,sr) * flag
     564
     565                sums_l_etot  = sums_l_etot + 0.5_wp * ( u(k,j,i)**2 + v(k,j,i)**2 + w(k,j,i)**2 )  &
     566                                             * rmask(j,i,sr) * flag
     567
     568!
     569!--             Computation of the Kolmogorov length scale. Calculation is based on gradients of the
     570!--             deviations from the horizontal mean.
    603571!--             Kolmogorov scale at the boundaries (k=0/z=0m and k=nzt+1) is set to zero.
    604572                IF ( kolmogorov_length_scale .AND. k /= nzb .AND. k /= nzt+1) THEN
     
    607575!
    608576!--                Calculate components of the fluctuating rate-of-strain tensor
    609 !--                (0.5*(del u'_i/del x_j + del u'_j/del x_i)) defined in the
    610 !--                center of each grid box.
    611                    du_dx = ( ( u(k,j,i+1) - hom(k,1,1,sr) ) -                  &
     577!--                (0.5*(del u'_i/del x_j + del u'_j/del x_i)) defined in the center of each grid
     578!--                box.
     579                   du_dx = ( ( u(k,j,i+1) - hom(k,1,1,sr) ) -                                      &
    612580                             ( u(k,j,i) - hom(k,1,1,sr) ) ) * ddx
    613                    du_dy = 0.25_wp * ddy *                                     &
    614                            ( ( u(k,j+1,i) - hom(k,1,1,sr) ) -                  &
    615                              ( u(k,j-1,i) - hom(k,1,1,sr) ) +                  &
    616                              ( u(k,j+1,i+1) - hom(k,1,1,sr) ) -                &
     581                   du_dy = 0.25_wp * ddy *                                                         &
     582                           ( ( u(k,j+1,i) - hom(k,1,1,sr) ) -                                      &
     583                             ( u(k,j-1,i) - hom(k,1,1,sr) ) +                                      &
     584                             ( u(k,j+1,i+1) - hom(k,1,1,sr) ) -                                    &
    617585                             ( u(k,j-1,i+1) - hom(k,1,1,sr) ) )
    618                    du_dz = 0.25_wp * ( ( ( u(k+1,j,i) - hom(k+1,1,1,sr) ) -    &
    619                                          ( u(k,j,i) - hom(k,1,1,sr) ) ) *      &
    620                                         ddzu(k+1) +                            &
    621                                        ( ( u(k,j,i) - hom(k,1,1,sr) ) -        &
    622                                          ( u(k-1,j,i) - hom(k-1,1,1,sr) ) )*   &
    623                                         ddzu(k) +                              &
    624                                        ( ( u(k+1,j,i+1) - hom(k+1,1,1,sr) )-   &
    625                                          ( u(k,j,i+1) - hom(k,1,1,sr) ) ) *    &
    626                                         ddzu(k+1) +                            &
    627                                        ( ( u(k,j,i+1) - hom(k,1,1,sr) ) -      &
    628                                          ( u(k-1,j,i+1) - hom(k-1,1,1,sr) ) ) *&
    629                                         ddzu(k) )
    630 
    631                    dv_dx = 0.25_wp * ddx *                                     &
    632                            ( ( v(k,j,i+1) - hom(k,1,2,sr) ) -                  &
    633                              ( v(k,j,i-1) - hom(k,1,2,sr) ) +                  &
    634                              ( v(k,j+1,i+1) - hom(k,1,2,sr) ) -                &
     586                   du_dz = 0.25_wp * ( ( ( u(k+1,j,i) - hom(k+1,1,1,sr) ) -                        &
     587                                         ( u(k,j,i) - hom(k,1,1,sr) ) ) *                          &
     588                                       ddzu(k+1) +                                                 &
     589                                       ( ( u(k,j,i) - hom(k,1,1,sr) ) -                            &
     590                                         ( u(k-1,j,i) - hom(k-1,1,1,sr) ) ) *                      &
     591                                       ddzu(k) +                                                   &
     592                                       ( ( u(k+1,j,i+1) - hom(k+1,1,1,sr) ) -                      &
     593                                         ( u(k,j,i+1) - hom(k,1,1,sr) ) ) *                        &
     594                                       ddzu(k+1) +                                                 &
     595                                       ( ( u(k,j,i+1) - hom(k,1,1,sr) ) -                          &
     596                                         ( u(k-1,j,i+1) - hom(k-1,1,1,sr) ) ) *                    &
     597                                       ddzu(k) )
     598
     599                   dv_dx = 0.25_wp * ddx *                                                         &
     600                           ( ( v(k,j,i+1) - hom(k,1,2,sr) ) -                                      &
     601                             ( v(k,j,i-1) - hom(k,1,2,sr) ) +                                      &
     602                             ( v(k,j+1,i+1) - hom(k,1,2,sr) ) -                                    &
    635603                             ( v(k,j+1,i-1) - hom(k,1,2,sr) ) )
    636                    dv_dy = ( ( v(k,j+1,i) - hom(k,1,2,sr) ) -                  &
    637                              ( v(k,j,i) - hom(k,1,2,sr) ) ) * ddy
    638                    dv_dz = 0.25_wp * ( ( ( v(k+1,j,i) - hom(k+1,1,2,sr) ) -    &
    639                                          ( v(k,j,i) - hom(k,1,2,sr) ) ) *      &
    640                                         ddzu(k+1) +                            &
    641                                        ( ( v(k,j,i) - hom(k,1,2,sr) ) -        &
    642                                          ( v(k-1,j,i) - hom(k-1,1,2,sr) ) ) *  &
    643                                         ddzu(k) +                              &
    644                                        ( ( v(k+1,j+1,i) - hom(k+1,1,2,sr) ) -  &
    645                                          ( v(k,j+1,i) - hom(k,1,2,sr) ) ) *    &
    646                                         ddzu(k+1) +                            &
    647                                        ( ( v(k,j+1,i) - hom(k,1,2,sr) ) -      &
    648                                          ( v(k-1,j+1,i) - hom(k-1,1,2,sr) ) ) *&
    649                                         ddzu(k) )
    650 
    651                    dw_dx = 0.25_wp * ddx * ( w(k,j,i+1) - w(k,j,i-1) +         &
    652                                              w(k-1,j,i+1) - w(k-1,j,i-1) )
    653                    dw_dy = 0.25_wp * ddy * ( w(k,j+1,i) - w(k,j-1,i) +         &
    654                                              w(k-1,j+1,i) - w(k-1,j-1,i) )
     604                   dv_dy = ( ( v(k,j+1,i) - hom(k,1,2,sr) ) - ( v(k,j,i) - hom(k,1,2,sr) ) ) * ddy
     605                   dv_dz = 0.25_wp * ( ( ( v(k+1,j,i) - hom(k+1,1,2,sr) ) -                        &
     606                                         ( v(k,j,i) - hom(k,1,2,sr) ) ) *                          &
     607                                       ddzu(k+1) +                                                 &
     608                                       ( ( v(k,j,i) - hom(k,1,2,sr) ) -                            &
     609                                         ( v(k-1,j,i) - hom(k-1,1,2,sr) ) ) *                      &
     610                                       ddzu(k) +                                                   &
     611                                       ( ( v(k+1,j+1,i) - hom(k+1,1,2,sr) ) -                      &
     612                                         ( v(k,j+1,i) - hom(k,1,2,sr) ) ) *                        &
     613                                       ddzu(k+1) +                                                 &
     614                                       ( ( v(k,j+1,i) - hom(k,1,2,sr) ) -                          &
     615                                         ( v(k-1,j+1,i) - hom(k-1,1,2,sr) ) ) *                    &
     616                                       ddzu(k) )
     617
     618                   dw_dx = 0.25_wp * ddx * ( w(k,j,i+1) - w(k,j,i-1) + w(k-1,j,i+1) - w(k-1,j,i-1) )
     619                   dw_dy = 0.25_wp * ddy * ( w(k,j+1,i) - w(k,j-1,i) + w(k-1,j+1,i) - w(k-1,j-1,i) )
    655620                   dw_dz = ( w(k,j,i) - w(k-1,j,i) ) * ddzw(k)
    656621
     
    667632                   s33 = 0.5_wp * ( dw_dz + dw_dz )
    668633
    669 !--                Calculate 3D instantaneous energy dissipation rate after
    670 !--                Pope (2000): Turbulent flows, p.259. It is defined in the center
    671 !--                of each grid volume.
    672                    dissipation = 2.0_wp * km(k,j,i) *                          &
    673                                 ( s11*s11 + s21*s21 + s31*s31 +                &
    674                                  s12*s12 + s22*s22 + s32*s32 +                 &
    675                                 s13*s13 + s23*s23 + s33*s33 )
     634!--                Calculate 3D instantaneous energy dissipation rate following Pope (2000):
     635!--                Turbulent flows, p.259. It is defined in the center of each grid volume.
     636                   dissipation = 2.0_wp * km(k,j,i) *                                              &
     637                                ( s11*s11 + s21*s21 + s31*s31 +                                    &
     638                                  s12*s12 + s22*s22 + s32*s32 +                                    &
     639                                  s13*s13 + s23*s23 + s33*s33 )
    676640                   eta         = ( km(k,j,i)**3.0_wp / ( dissipation+1.0E-12 ) )**(1.0_wp/4.0_wp)
    677641
    678642                   !$ACC ATOMIC
    679                    sums_l(k,121,tn) = sums_l(k,121,tn) + eta * rmask(j,i,sr)   &
    680                                                                 * flag
     643                   sums_l(k,121,tn) = sums_l(k,121,tn) + eta * rmask(j,i,sr) * flag
    681644
    682645
     
    685648             ENDDO !k-loop
    686649!
    687 !--          Total and perturbation energy for the total domain (being
    688 !--          collected in the last column of sums_l). Summation of these
    689 !--          quantities is seperated from the previous loop in order to
    690 !--          allow vectorization of that loop.
     650!--          Total and perturbation energy for the total domain (being collected in the last column
     651!--          of sums_l). Summation of these quantities is seperated from the previous loop in order
     652!--          to allow vectorization of that loop.
    691653             !$ACC ATOMIC
    692654             sums_l(nzb+4,pr_palm,tn) = sums_l(nzb+4,pr_palm,tn) + sums_l_etot
    693655!
    694656!--          2D-arrays (being collected in the last column of sums_l)
    695              IF ( surf_def_h(0)%end_index(j,i) >=                              &
    696                   surf_def_h(0)%start_index(j,i) )  THEN
     657             IF ( surf_def_h(0)%end_index(j,i) >= surf_def_h(0)%start_index(j,i) )  THEN
    697658                m = surf_def_h(0)%start_index(j,i)
    698659                !$ACC ATOMIC
    699                 sums_l(nzb,pr_palm,tn)   = sums_l(nzb,pr_palm,tn) +            &
    700                                         surf_def_h(0)%us(m)   * rmask(j,i,sr)
    701                 !$ACC ATOMIC
    702                 sums_l(nzb+1,pr_palm,tn) = sums_l(nzb+1,pr_palm,tn) +          &
    703                                         surf_def_h(0)%usws(m) * rmask(j,i,sr)
    704                 !$ACC ATOMIC
    705                 sums_l(nzb+2,pr_palm,tn) = sums_l(nzb+2,pr_palm,tn) +          &
    706                                         surf_def_h(0)%vsws(m) * rmask(j,i,sr)
    707                 !$ACC ATOMIC
    708                 sums_l(nzb+3,pr_palm,tn) = sums_l(nzb+3,pr_palm,tn) +          &
    709                                         surf_def_h(0)%ts(m)   * rmask(j,i,sr)
     660                sums_l(nzb,pr_palm,tn)   = sums_l(nzb,pr_palm,tn) +                                &
     661                                           surf_def_h(0)%us(m)   * rmask(j,i,sr)
     662                !$ACC ATOMIC
     663                sums_l(nzb+1,pr_palm,tn) = sums_l(nzb+1,pr_palm,tn) +                              &
     664                                           surf_def_h(0)%usws(m) * rmask(j,i,sr)
     665                !$ACC ATOMIC
     666                sums_l(nzb+2,pr_palm,tn) = sums_l(nzb+2,pr_palm,tn) +                              &
     667                                           surf_def_h(0)%vsws(m) * rmask(j,i,sr)
     668                !$ACC ATOMIC
     669                sums_l(nzb+3,pr_palm,tn) = sums_l(nzb+3,pr_palm,tn) +                              &
     670                                           surf_def_h(0)%ts(m)   * rmask(j,i,sr)
    710671#ifndef _OPENACC
    711672                IF ( humidity )  THEN
    712                    sums_l(nzb+12,pr_palm,tn) = sums_l(nzb+12,pr_palm,tn) +     &
    713                                             surf_def_h(0)%qs(m)   * rmask(j,i,sr)
     673                   sums_l(nzb+12,pr_palm,tn) = sums_l(nzb+12,pr_palm,tn) +                         &
     674                                               surf_def_h(0)%qs(m)   * rmask(j,i,sr)
    714675                ENDIF
    715676                IF ( passive_scalar )  THEN
    716                    sums_l(nzb+13,pr_palm,tn) = sums_l(nzb+13,pr_palm,tn) +     &
    717                                             surf_def_h(0)%ss(m)   * rmask(j,i,sr)
     677                   sums_l(nzb+13,pr_palm,tn) = sums_l(nzb+13,pr_palm,tn) +                         &
     678                                               surf_def_h(0)%ss(m)   * rmask(j,i,sr)
    718679                ENDIF
    719680#endif
     
    721682!--             Summation of surface temperature.
    722683                !$ACC ATOMIC
    723                 sums_l(nzb+14,pr_palm,tn) = sums_l(nzb+14,pr_palm,tn)   +      &
    724                                             surf_def_h(0)%pt_surface(m) *      &
    725                                             rmask(j,i,sr)
     684                sums_l(nzb+14,pr_palm,tn) = sums_l(nzb+14,pr_palm,tn)   +                          &
     685                                            surf_def_h(0)%pt_surface(m) * rmask(j,i,sr)
    726686             ENDIF
    727687             IF ( surf_lsm_h%end_index(j,i) >= surf_lsm_h%start_index(j,i) )  THEN
    728688                m = surf_lsm_h%start_index(j,i)
    729689                !$ACC ATOMIC
    730                 sums_l(nzb,pr_palm,tn)   = sums_l(nzb,pr_palm,tn) +            &
    731                                         surf_lsm_h%us(m)   * rmask(j,i,sr)
    732                 !$ACC ATOMIC
    733                 sums_l(nzb+1,pr_palm,tn) = sums_l(nzb+1,pr_palm,tn) +          &
    734                                         surf_lsm_h%usws(m) * rmask(j,i,sr)
    735                 !$ACC ATOMIC
    736                 sums_l(nzb+2,pr_palm,tn) = sums_l(nzb+2,pr_palm,tn) +          &
    737                                         surf_lsm_h%vsws(m) * rmask(j,i,sr)
    738                 !$ACC ATOMIC
    739                 sums_l(nzb+3,pr_palm,tn) = sums_l(nzb+3,pr_palm,tn) +          &
    740                                         surf_lsm_h%ts(m)   * rmask(j,i,sr)
     690                sums_l(nzb,pr_palm,tn)   = sums_l(nzb,pr_palm,tn) +                                &
     691                                           surf_lsm_h%us(m)   * rmask(j,i,sr)
     692                !$ACC ATOMIC
     693                sums_l(nzb+1,pr_palm,tn) = sums_l(nzb+1,pr_palm,tn) +                              &
     694                                           surf_lsm_h%usws(m) * rmask(j,i,sr)
     695                !$ACC ATOMIC
     696                sums_l(nzb+2,pr_palm,tn) = sums_l(nzb+2,pr_palm,tn) +                              &
     697                                           surf_lsm_h%vsws(m) * rmask(j,i,sr)
     698                !$ACC ATOMIC
     699                sums_l(nzb+3,pr_palm,tn) = sums_l(nzb+3,pr_palm,tn) +                              &
     700                                           surf_lsm_h%ts(m)   * rmask(j,i,sr)
    741701#ifndef _OPENACC
    742702                IF ( humidity )  THEN
    743                    sums_l(nzb+12,pr_palm,tn) = sums_l(nzb+12,pr_palm,tn) +     &
    744                                             surf_lsm_h%qs(m)   * rmask(j,i,sr)
     703                   sums_l(nzb+12,pr_palm,tn) = sums_l(nzb+12,pr_palm,tn) +                         &
     704                                               surf_lsm_h%qs(m)   * rmask(j,i,sr)
    745705                ENDIF
    746706                IF ( passive_scalar )  THEN
    747                    sums_l(nzb+13,pr_palm,tn) = sums_l(nzb+13,pr_palm,tn) +     &
    748                                             surf_lsm_h%ss(m)   * rmask(j,i,sr)
     707                   sums_l(nzb+13,pr_palm,tn) = sums_l(nzb+13,pr_palm,tn) +                         &
     708                                               surf_lsm_h%ss(m)   * rmask(j,i,sr)
    749709                ENDIF
    750710#endif
     
    752712!--             Summation of surface temperature.
    753713                !$ACC ATOMIC
    754                 sums_l(nzb+14,pr_palm,tn) = sums_l(nzb+14,pr_palm,tn)   +      &
    755                                             surf_lsm_h%pt_surface(m)    *      &
    756                                             rmask(j,i,sr)
     714                sums_l(nzb+14,pr_palm,tn) = sums_l(nzb+14,pr_palm,tn) +                            &
     715                                            surf_lsm_h%pt_surface(m) * rmask(j,i,sr)
    757716             ENDIF
    758717             IF ( surf_usm_h%end_index(j,i) >= surf_usm_h%start_index(j,i) )  THEN
    759718                m = surf_usm_h%start_index(j,i)
    760719                !$ACC ATOMIC
    761                 sums_l(nzb,pr_palm,tn)   = sums_l(nzb,pr_palm,tn) +            &
    762                                         surf_usm_h%us(m)   * rmask(j,i,sr)
    763                 !$ACC ATOMIC
    764                 sums_l(nzb+1,pr_palm,tn) = sums_l(nzb+1,pr_palm,tn) +          &
    765                                         surf_usm_h%usws(m) * rmask(j,i,sr)
    766                 !$ACC ATOMIC
    767                 sums_l(nzb+2,pr_palm,tn) = sums_l(nzb+2,pr_palm,tn) +          &
    768                                         surf_usm_h%vsws(m) * rmask(j,i,sr)
    769                 !$ACC ATOMIC
    770                 sums_l(nzb+3,pr_palm,tn) = sums_l(nzb+3,pr_palm,tn) +          &
    771                                         surf_usm_h%ts(m)   * rmask(j,i,sr)
     720                sums_l(nzb,pr_palm,tn)   = sums_l(nzb,pr_palm,tn) +                                &
     721                                           surf_usm_h%us(m)   * rmask(j,i,sr)
     722                !$ACC ATOMIC
     723                sums_l(nzb+1,pr_palm,tn) = sums_l(nzb+1,pr_palm,tn) +                              &
     724                                           surf_usm_h%usws(m) * rmask(j,i,sr)
     725                !$ACC ATOMIC
     726                sums_l(nzb+2,pr_palm,tn) = sums_l(nzb+2,pr_palm,tn) +                              &
     727                                           surf_usm_h%vsws(m) * rmask(j,i,sr)
     728                !$ACC ATOMIC
     729                sums_l(nzb+3,pr_palm,tn) = sums_l(nzb+3,pr_palm,tn) +                              &
     730                                           surf_usm_h%ts(m)   * rmask(j,i,sr)
    772731#ifndef _OPENACC
    773732                IF ( humidity )  THEN
    774                    sums_l(nzb+12,pr_palm,tn) = sums_l(nzb+12,pr_palm,tn) +     &
    775                                             surf_usm_h%qs(m)   * rmask(j,i,sr)
     733                   sums_l(nzb+12,pr_palm,tn) = sums_l(nzb+12,pr_palm,tn) +                         &
     734                                               surf_usm_h%qs(m)   * rmask(j,i,sr)
    776735                ENDIF
    777736                IF ( passive_scalar )  THEN
    778                    sums_l(nzb+13,pr_palm,tn) = sums_l(nzb+13,pr_palm,tn) +     &
    779                                             surf_usm_h%ss(m)  * rmask(j,i,sr)
     737                   sums_l(nzb+13,pr_palm,tn) = sums_l(nzb+13,pr_palm,tn) +                         &
     738                                               surf_usm_h%ss(m) * rmask(j,i,sr)
    780739                ENDIF
    781740#endif
     
    783742!--             Summation of surface temperature.
    784743                !$ACC ATOMIC
    785                 sums_l(nzb+14,pr_palm,tn) = sums_l(nzb+14,pr_palm,tn)   +      &
    786                                             surf_usm_h%pt_surface(m)    *      &
    787                                             rmask(j,i,sr)
     744                sums_l(nzb+14,pr_palm,tn) = sums_l(nzb+14,pr_palm,tn) +                            &
     745                                            surf_usm_h%pt_surface(m)  * rmask(j,i,sr)
    788746             ENDIF
    789747          ENDDO !j-loop
     
    798756!--    Computation of statistics when ws-scheme is not used. Else these
    799757!--    quantities are evaluated in the advection routines.
    800        IF ( .NOT. ws_scheme_mom .OR. sr /= 0 .OR. simulated_time == 0.0_wp )   &
    801        THEN
     758       IF ( .NOT. ws_scheme_mom .OR. sr /= 0 .OR. simulated_time == 0.0_wp )  THEN
    802759          !$OMP DO
    803760          DO  i = nxl, nxr
     
    812769                   vst2 = ( v(k,j,i) - hom(k,1,2,sr) )**2
    813770
    814                    sums_l(k,30,tn) = sums_l(k,30,tn) + ust2 * rmask(j,i,sr)    &
    815                                                             * flag
    816                    sums_l(k,31,tn) = sums_l(k,31,tn) + vst2 * rmask(j,i,sr)    &
    817                                                             * flag
    818                    sums_l(k,32,tn) = sums_l(k,32,tn) + w2   * rmask(j,i,sr)    &
    819                                                             * flag
     771                   sums_l(k,30,tn) = sums_l(k,30,tn) + ust2 * rmask(j,i,sr) * flag
     772                   sums_l(k,31,tn) = sums_l(k,31,tn) + vst2 * rmask(j,i,sr) * flag
     773                   sums_l(k,32,tn) = sums_l(k,32,tn) + w2   * rmask(j,i,sr) * flag
    820774!
    821775!--                Perturbation energy
    822 
    823                    sums_l(k,34,tn) = sums_l(k,34,tn) + 0.5_wp *                &
    824                                   ( ust2 + vst2 + w2 )      * rmask(j,i,sr)    &
    825                                                             * flag
     776                   sums_l(k,34,tn) = sums_l(k,34,tn) +                                             &
     777                                     0.5_wp * ( ust2 + vst2 + w2 ) * rmask(j,i,sr) * flag
    826778                ENDDO
    827779             ENDDO
     
    829781       ENDIF
    830782!
    831 !--    Computaion of domain-averaged perturbation energy. Please note,
    832 !--    to prevent that perturbation energy is larger (even if only slightly)
    833 !--    than the total kinetic energy, calculation is based on deviations from
    834 !--    the horizontal mean, instead of spatial descretization of the advection
     783!--    Computaion of domain-averaged perturbation energy. Please note, to prevent that perturbation
     784!--    energy is larger (even if only slightly) than the total kinetic energy, calculation is based
     785!--    on deviations from the horizontal mean, instead of spatial descretization of the advection
    835786!--    term.
    836787       !$OMP DO
     
    849800
    850801                !$ACC ATOMIC
    851                 sums_l(nzb+5,pr_palm,tn) = sums_l(nzb+5,pr_palm,tn)            &
    852                                  + 0.5_wp * ( ust2 + vst2 + w2 )               &
    853                                  * rmask(j,i,sr)                               &
    854                                  * flag
     802                sums_l(nzb+5,pr_palm,tn) = sums_l(nzb+5,pr_palm,tn)                                &
     803                                           + 0.5_wp * ( ust2 + vst2 + w2 ) * rmask(j,i,sr) * flag
    855804
    856805             ENDDO
     
    861810!
    862811!--    Horizontally averaged profiles of the vertical fluxes
    863 
    864812       !$OMP DO
    865813       !$ACC PARALLEL LOOP COLLAPSE(2) PRIVATE(i, j, k, l, m) &
     
    873821          DO  j = nys, nyn
    874822!
    875 !--          Subgridscale fluxes (without Prandtl layer from k=nzb,
    876 !--          oterwise from k=nzb+1)
    877 !--          NOTE: for simplicity, nzb_diff_s_inner is used below, although
    878 !--          ----  strictly speaking the following k-loop would have to be
    879 !--                split up according to the staggered grid.
    880 !--                However, this implies no error since staggered velocity
    881 !--                components are zero at the walls and inside buildings.
    882 !--          Flag 23 is used to mask surface fluxes as well as model-top fluxes,
    883 !--          which are added further below.
     823!--          Subgridscale fluxes (without Prandtl layer from k=nzb, oterwise from k=nzb+1)
     824!--          NOTE: for simplicity, nzb_diff_s_inner is used below, although strictly speaking the
     825!--          ----  following k-loop would have to be split up according to the staggered grid.
     826!--                However, this implies no error since staggered velocity components are zero at
     827!--                the walls and inside buildings.
     828!--          Flag 23 is used to mask surface fluxes as well as model-top fluxes, which are added
     829!--          further below.
    884830             DO  k = nzb, nzt
    885                 flag = MERGE( 1.0_wp, 0.0_wp,                                  &
    886                               BTEST( wall_flags_total_0(k,j,i), 23 ) ) *       &
    887                        MERGE( 1.0_wp, 0.0_wp,                                  &
    888                               BTEST( wall_flags_total_0(k,j,i), 9  ) )
     831                flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 23 ) ) *           &
     832                       MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 9  ) )
    889833!
    890834!--             Momentum flux w"u"
    891835                !$ACC ATOMIC
    892                 sums_l(k,12,tn) = sums_l(k,12,tn) - 0.25_wp * (                &
    893                                km(k,j,i)+km(k+1,j,i)+km(k,j,i-1)+km(k+1,j,i-1) &
    894                                                            ) * (               &
    895                                    ( u(k+1,j,i) - u(k,j,i)   ) * ddzu(k+1)     &
    896                                  + ( w(k,j,i)   - w(k,j,i-1) ) * ddx           &
    897                                                            ) * rmask(j,i,sr)   &
    898                                          * rho_air_zw(k)                       &
    899                                          * momentumflux_output_conversion(k)   &
    900                                          * flag
     836                sums_l(k,12,tn) = sums_l(k,12,tn) - 0.25_wp * (                                    &
     837                                  km(k,j,i) + km(k+1,j,i) + km(k,j,i-1) + km(k+1,j,i-1)            &
     838                                                              ) * (                                &
     839                                      ( u(k+1,j,i) - u(k,j,i)   ) * ddzu(k+1)                      &
     840                                    + ( w(k,j,i)   - w(k,j,i-1) ) * ddx                            &
     841                                                                  ) * rmask(j,i,sr)                &
     842                                            * rho_air_zw(k)                                        &
     843                                            * momentumflux_output_conversion(k)                    &
     844                                            * flag
    901845!
    902846!--             Momentum flux w"v"
    903847                !$ACC ATOMIC
    904                 sums_l(k,14,tn) = sums_l(k,14,tn) - 0.25_wp * (                &
    905                                km(k,j,i)+km(k+1,j,i)+km(k,j-1,i)+km(k+1,j-1,i) &
    906                                                            ) * (               &
    907                                    ( v(k+1,j,i) - v(k,j,i)   ) * ddzu(k+1)     &
    908                                  + ( w(k,j,i)   - w(k,j-1,i) ) * ddy           &
    909                                                            ) * rmask(j,i,sr)   &
    910                                          * rho_air_zw(k)                       &
    911                                          * momentumflux_output_conversion(k)   &
    912                                          * flag
     848                sums_l(k,14,tn) = sums_l(k,14,tn) - 0.25_wp * (                                    &
     849                                  km(k,j,i) + km(k+1,j,i) + km(k,j-1,i) + km(k+1,j-1,i)            &
     850                                                              ) * (                                &
     851                                      ( v(k+1,j,i) - v(k,j,i)   ) * ddzu(k+1)                      &
     852                                    + ( w(k,j,i)   - w(k,j-1,i) ) * ddy                            &
     853                                                                  ) * rmask(j,i,sr)                &
     854                                            * rho_air_zw(k)                                        &
     855                                            * momentumflux_output_conversion(k)                    &
     856                                            * flag
    913857!
    914858!--             Heat flux w"pt"
    915859                !$ACC ATOMIC
    916                 sums_l(k,16,tn) = sums_l(k,16,tn)                              &
    917                                          - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )&
    918                                                * ( pt(k+1,j,i) - pt(k,j,i) )   &
    919                                                * rho_air_zw(k)                 &
    920                                                * heatflux_output_conversion(k) &
    921                                                * ddzu(k+1) * rmask(j,i,sr)     &
     860                sums_l(k,16,tn) = sums_l(k,16,tn)                                                  &
     861                                         - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )                    &
     862                                               * ( pt(k+1,j,i) - pt(k,j,i) )                       &
     863                                               * rho_air_zw(k)                                     &
     864                                               * heatflux_output_conversion(k)                     &
     865                                               * ddzu(k+1) * rmask(j,i,sr)                         &
    922866                                               * flag
    923867
     
    926870#ifndef _OPENACC
    927871                IF ( ocean_mode )  THEN
    928                    sums_l(k,65,tn) = sums_l(k,65,tn)                           &
    929                                          - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )&
    930                                                * ( sa(k+1,j,i) - sa(k,j,i) )   &
    931                                                * ddzu(k+1) * rmask(j,i,sr)     &
     872                   sums_l(k,65,tn) = sums_l(k,65,tn)                                               &
     873                                         - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )                    &
     874                                               * ( sa(k+1,j,i) - sa(k,j,i) )                       &
     875                                               * ddzu(k+1) * rmask(j,i,sr)                         &
    932876                                               * flag
    933877                ENDIF
     
    936880!--             Buoyancy flux, water flux (humidity flux) w"q"
    937881                IF ( humidity ) THEN
    938                    sums_l(k,45,tn) = sums_l(k,45,tn)                           &
    939                                          - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )&
    940                                                * ( vpt(k+1,j,i) - vpt(k,j,i) ) &
    941                                                * rho_air_zw(k)                 &
    942                                                * heatflux_output_conversion(k) &
     882                   sums_l(k,45,tn) = sums_l(k,45,tn)                                               &
     883                                         - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )                    &
     884                                               * ( vpt(k+1,j,i) - vpt(k,j,i) )                     &
     885                                               * rho_air_zw(k)                                     &
     886                                               * heatflux_output_conversion(k)                     &
    943887                                               * ddzu(k+1) * rmask(j,i,sr) * flag
    944                    sums_l(k,48,tn) = sums_l(k,48,tn)                           &
    945                                          - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )&
    946                                                * ( q(k+1,j,i) - q(k,j,i) )     &
    947                                                * rho_air_zw(k)                 &
    948                                                * waterflux_output_conversion(k)&
     888                   sums_l(k,48,tn) = sums_l(k,48,tn)                                               &
     889                                         - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )                    &
     890                                               * ( q(k+1,j,i) - q(k,j,i) )                         &
     891                                               * rho_air_zw(k)                                     &
     892                                               * waterflux_output_conversion(k)                    &
    949893                                               * ddzu(k+1) * rmask(j,i,sr) * flag
    950894
    951895                   IF ( bulk_cloud_model ) THEN
    952                       sums_l(k,51,tn) = sums_l(k,51,tn)                        &
    953                                          - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )&
    954                                                * ( ( q(k+1,j,i) - ql(k+1,j,i) )&
    955                                                 - ( q(k,j,i) - ql(k,j,i) ) )   &
    956                                                * rho_air_zw(k)                 &
    957                                                * waterflux_output_conversion(k)&
     896                      sums_l(k,51,tn) = sums_l(k,51,tn)                                            &
     897                                         - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )                    &
     898                                               * ( ( q(k+1,j,i) - ql(k+1,j,i) )                    &
     899                                                - ( q(k,j,i) - ql(k,j,i) ) )                       &
     900                                               * rho_air_zw(k)                                     &
     901                                               * waterflux_output_conversion(k)                    &
    958902                                               * ddzu(k+1) * rmask(j,i,sr) * flag
    959903                   ENDIF
     
    963907!--             Passive scalar flux
    964908                IF ( passive_scalar )  THEN
    965                    sums_l(k,117,tn) = sums_l(k,117,tn)                         &
    966                                          - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )&
    967                                                   * ( s(k+1,j,i) - s(k,j,i) )  &
    968                                                   * ddzu(k+1) * rmask(j,i,sr)  &
     909                   sums_l(k,117,tn) = sums_l(k,117,tn)                                             &
     910                                         - 0.5_wp * ( kh(k,j,i) + kh(k+1,j,i) )                    &
     911                                                  * ( s(k+1,j,i) - s(k,j,i) )                      &
     912                                                  * ddzu(k+1) * rmask(j,i,sr)                      &
    969913                                                              * flag
    970914                ENDIF
     
    983927                   ki = -1 + l
    984928                   IF ( surf_def_h(l)%ns >= 1 )  THEN
    985                       DO  m = surf_def_h(l)%start_index(j,i),                  &
     929                      DO  m = surf_def_h(l)%start_index(j,i),                                      &
    986930                              surf_def_h(l)%end_index(j,i)
    987931                         k = surf_def_h(l)%k(m)
    988932
    989933                         !$ACC ATOMIC
    990                          sums_l(k+ki,12,tn) = sums_l(k+ki,12,tn) + &
    991                                     momentumflux_output_conversion(k+ki) * &
    992                                     surf_def_h(l)%usws(m) * rmask(j,i,sr)     ! w"u"
     934                         sums_l(k+ki,12,tn) = sums_l(k+ki,12,tn) +                                 &
     935                                              momentumflux_output_conversion(k+ki) *              &
     936                                              surf_def_h(l)%usws(m) * rmask(j,i,sr)     ! w"u"
    993937                         !$ACC ATOMIC
    994                          sums_l(k+ki,14,tn) = sums_l(k+ki,14,tn) + &
    995                                     momentumflux_output_conversion(k+ki) * &
    996                                     surf_def_h(l)%vsws(m) * rmask(j,i,sr)     ! w"v"
     938                         sums_l(k+ki,14,tn) = sums_l(k+ki,14,tn) +                                 &
     939                                              momentumflux_output_conversion(k+ki) *              &
     940                                              surf_def_h(l)%vsws(m) * rmask(j,i,sr)     ! w"v"
    997941                         !$ACC ATOMIC
    998                          sums_l(k+ki,16,tn) = sums_l(k+ki,16,tn) + &
    999                                     heatflux_output_conversion(k+ki) * &
    1000                                     surf_def_h(l)%shf(m)  * rmask(j,i,sr)     ! w"pt"
     942                         sums_l(k+ki,16,tn) = sums_l(k+ki,16,tn) +                                 &
     943                                              heatflux_output_conversion(k+ki) *                  &
     944                                              surf_def_h(l)%shf(m)  * rmask(j,i,sr)     ! w"pt"
    1001945#if 0
    1002                          sums_l(k+ki,58,tn) = sums_l(k+ki,58,tn) + &
    1003                                     0.0_wp * rmask(j,i,sr)        ! u"pt"
    1004                          sums_l(k+ki,61,tn) = sums_l(k+ki,61,tn) + &
    1005                                     0.0_wp * rmask(j,i,sr)        ! v"pt"
     946                         sums_l(k+ki,58,tn) = sums_l(k+ki,58,tn) +                                 &
     947                                              0.0_wp * rmask(j,i,sr)                    ! u"pt"
     948                         sums_l(k+ki,61,tn) = sums_l(k+ki,61,tn) +                                 &
     949                                              0.0_wp * rmask(j,i,sr)                    ! v"pt"
    1006950#endif
    1007951#ifndef _OPENACC
    1008952                         IF ( ocean_mode )  THEN
    1009                             sums_l(k+ki,65,tn) = sums_l(k+ki,65,tn) + &
    1010                                        surf_def_h(l)%sasws(m) * rmask(j,i,sr)  ! w"sa"
     953                            sums_l(k+ki,65,tn) = sums_l(k+ki,65,tn) +                              &
     954                                                 surf_def_h(l)%sasws(m) * rmask(j,i,sr)  ! w"sa"
    1011955                         ENDIF
    1012956                         IF ( humidity )  THEN
    1013                             sums_l(k+ki,48,tn) = sums_l(k+ki,48,tn) +                     &
    1014                                        waterflux_output_conversion(k+ki) *      &
    1015                                        surf_def_h(l)%qsws(m) * rmask(j,i,sr)  ! w"q" (w"qv")
    1016                             sums_l(k+ki,45,tn) = sums_l(k+ki,45,tn) + (                   &
    1017                                        ( 1.0_wp + 0.61_wp * q(k+ki,j,i) ) *     &
    1018                                        surf_def_h(l)%shf(m) + 0.61_wp * pt(k+ki,j,i) *      &
    1019                                                   surf_def_h(l)%qsws(m) )                  &
    1020                                        * heatflux_output_conversion(k+ki)
     957                            sums_l(k+ki,48,tn) = sums_l(k+ki,48,tn) +                              &
     958                                                 waterflux_output_conversion(k+ki) *               &
     959                                                 surf_def_h(l)%qsws(m) * rmask(j,i,sr)  ! w"q" (w"qv")
     960                            sums_l(k+ki,45,tn) = sums_l(k+ki,45,tn) +  (                           &
     961                                                 ( 1.0_wp + 0.61_wp * q(k+ki,j,i) ) *              &
     962                                                 surf_def_h(l)%shf(m) + 0.61_wp * pt(k+ki,j,i) *   &
     963                                                 surf_def_h(l)%qsws(m) )                           &
     964                                                 * heatflux_output_conversion(k+ki)
    1021965                            IF ( cloud_droplets )  THEN
    1022                                sums_l(k+ki,45,tn) = sums_l(k+ki,45,tn) + (                &
    1023                                          ( 1.0_wp + 0.61_wp * q(k+ki,j,i) -     &
    1024                                            ql(k+ki,j,i) ) * surf_def_h(l)%shf(m) +          &
    1025                                            0.61_wp * pt(k+ki,j,i) * surf_def_h(l)%qsws(m) ) &
    1026                                           * heatflux_output_conversion(k+ki)
     966                               sums_l(k+ki,45,tn) = sums_l(k+ki,45,tn) +      (                    &
     967                                                    ( 1.0_wp + 0.61_wp * q(k+ki,j,i) -             &
     968                                                      ql(k+ki,j,i) ) * surf_def_h(l)%shf(m) +      &
     969                                                      0.61_wp * pt(k+ki,j,i)                       &
     970                                                      * surf_def_h(l)%qsws(m) )                    &
     971                                                    * heatflux_output_conversion(k+ki)
    1027972                            ENDIF
    1028973                            IF ( bulk_cloud_model )  THEN
    1029974!
    1030975!--                            Formula does not work if ql(k+ki) /= 0.0
    1031                                sums_l(k+ki,51,tn) = sums_l(k+ki,51,tn) +                  &
    1032                                           waterflux_output_conversion(k+ki) *   &
    1033                                           surf_def_h(l)%qsws(m) * rmask(j,i,sr) ! w"q" (w"qv")
     976                               sums_l(k+ki,51,tn) = sums_l(k+ki,51,tn) +                           &
     977                                                    waterflux_output_conversion(k+ki) *            &
     978                                                    surf_def_h(l)%qsws(m) * rmask(j,i,sr) ! w"q" (w"qv")
    1034979                            ENDIF
    1035980                         ENDIF
    1036981                         IF ( passive_scalar )  THEN
    1037                             sums_l(k+ki,117,tn) = sums_l(k+ki,117,tn) +                     &
    1038                                         surf_def_h(l)%ssws(m) * rmask(j,i,sr) ! w"s"
     982                            sums_l(k+ki,117,tn) = sums_l(k+ki,117,tn) +                            &
     983                                                  surf_def_h(l)%ssws(m) * rmask(j,i,sr) ! w"s"
    1039984                         ENDIF
    1040985#endif
     
    1044989                   ENDIF
    1045990                ENDDO
    1046                 IF ( surf_lsm_h%end_index(j,i) >=                              &
    1047                      surf_lsm_h%start_index(j,i) )  THEN
     991                IF ( surf_lsm_h%end_index(j,i) >= surf_lsm_h%start_index(j,i) )  THEN
    1048992                   m = surf_lsm_h%start_index(j,i)
    1049993                   !$ACC ATOMIC
    1050                    sums_l(nzb,12,tn) = sums_l(nzb,12,tn) + &
    1051                                     momentumflux_output_conversion(nzb) * &
    1052                                     surf_lsm_h%usws(m) * rmask(j,i,sr)     ! w"u"
     994                   sums_l(nzb,12,tn) = sums_l(nzb,12,tn) +                                         &
     995                                       momentumflux_output_conversion(nzb) *                      &
     996                                       surf_lsm_h%usws(m) * rmask(j,i,sr)     ! w"u"
    1053997                   !$ACC ATOMIC
    1054                    sums_l(nzb,14,tn) = sums_l(nzb,14,tn) + &
    1055                                     momentumflux_output_conversion(nzb) * &
    1056                                     surf_lsm_h%vsws(m) * rmask(j,i,sr)     ! w"v"
     998                   sums_l(nzb,14,tn) = sums_l(nzb,14,tn) +                                         &
     999                                       momentumflux_output_conversion(nzb) *                      &
     1000                                       surf_lsm_h%vsws(m) * rmask(j,i,sr)     ! w"v"
    10571001                   !$ACC ATOMIC
    1058                    sums_l(nzb,16,tn) = sums_l(nzb,16,tn) + &
    1059                                     heatflux_output_conversion(nzb) * &
    1060                                     surf_lsm_h%shf(m)  * rmask(j,i,sr)     ! w"pt"
     1002                   sums_l(nzb,16,tn) = sums_l(nzb,16,tn) +                                         &
     1003                                       heatflux_output_conversion(nzb) *                          &
     1004                                       surf_lsm_h%shf(m)  * rmask(j,i,sr)     ! w"pt"
    10611005#if 0
    1062                    sums_l(nzb,58,tn) = sums_l(nzb,58,tn) + &
    1063                                     0.0_wp * rmask(j,i,sr)        ! u"pt"
    1064                    sums_l(nzb,61,tn) = sums_l(nzb,61,tn) + &
    1065                                     0.0_wp * rmask(j,i,sr)        ! v"pt"
     1006                   sums_l(nzb,58,tn) = sums_l(nzb,58,tn) +                                         &
     1007                                       0.0_wp * rmask(j,i,sr)        ! u"pt"
     1008                   sums_l(nzb,61,tn) = sums_l(nzb,61,tn) +                                         &
     1009                                       0.0_wp * rmask(j,i,sr)        ! v"pt"
    10661010#endif
    10671011#ifndef _OPENACC
    10681012                   IF ( ocean_mode )  THEN
    1069                       sums_l(nzb,65,tn) = sums_l(nzb,65,tn) + &
    1070                                        surf_lsm_h%sasws(m) * rmask(j,i,sr)  ! w"sa"
     1013                      sums_l(nzb,65,tn) = sums_l(nzb,65,tn) +                                      &
     1014                                          surf_lsm_h%sasws(m) * rmask(j,i,sr)  ! w"sa"
    10711015                   ENDIF
    10721016                   IF ( humidity )  THEN
    1073                       sums_l(nzb,48,tn) = sums_l(nzb,48,tn) +                     &
    1074                                        waterflux_output_conversion(nzb) *      &
    1075                                        surf_lsm_h%qsws(m) * rmask(j,i,sr)  ! w"q" (w"qv")
    1076                       sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                   &
    1077                                        ( 1.0_wp + 0.61_wp * q(nzb,j,i) ) *     &
    1078                                        surf_lsm_h%shf(m) + 0.61_wp * pt(nzb,j,i) *      &
    1079                                                   surf_lsm_h%qsws(m) )                  &
    1080                                        * heatflux_output_conversion(nzb)
     1017                      sums_l(nzb,48,tn) = sums_l(nzb,48,tn) +                                      &
     1018                                          waterflux_output_conversion(nzb) *                       &
     1019                                          surf_lsm_h%qsws(m) * rmask(j,i,sr)  ! w"q" (w"qv")
     1020                      sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                                    &
     1021                                          ( 1.0_wp + 0.61_wp * q(nzb,j,i) ) * surf_lsm_h%shf(m) +  &
     1022                                            0.61_wp * pt(nzb,j,i) * surf_lsm_h%qsws(m) )           &
     1023                                          * heatflux_output_conversion(nzb)
    10811024                      IF ( cloud_droplets )  THEN
    1082                          sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                &
    1083                                          ( 1.0_wp + 0.61_wp * q(nzb,j,i) -     &
    1084                                            ql(nzb,j,i) ) * surf_lsm_h%shf(m) +          &
    1085                                            0.61_wp * pt(nzb,j,i) * surf_lsm_h%qsws(m) ) &
    1086                                           * heatflux_output_conversion(nzb)
     1025                         sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                                 &
     1026                                             ( 1.0_wp + 0.61_wp * q(nzb,j,i) -                     &
     1027                                               ql(nzb,j,i) ) * surf_lsm_h%shf(m) +                 &
     1028                                               0.61_wp * pt(nzb,j,i) * surf_lsm_h%qsws(m) )        &
     1029                                             * heatflux_output_conversion(nzb)
    10871030                      ENDIF
    10881031                      IF ( bulk_cloud_model )  THEN
    10891032!
    10901033!--                      Formula does not work if ql(nzb) /= 0.0
    1091                          sums_l(nzb,51,tn) = sums_l(nzb,51,tn) +                  &
    1092                                           waterflux_output_conversion(nzb) *   &
    1093                                           surf_lsm_h%qsws(m) * rmask(j,i,sr) ! w"q" (w"qv")
     1034                         sums_l(nzb,51,tn) = sums_l(nzb,51,tn) +                                   &
     1035                                             waterflux_output_conversion(nzb) *                    &
     1036                                             surf_lsm_h%qsws(m) * rmask(j,i,sr) ! w"q" (w"qv")
    10941037                      ENDIF
    10951038                   ENDIF
    10961039                   IF ( passive_scalar )  THEN
    1097                       sums_l(nzb,117,tn) = sums_l(nzb,117,tn) +                     &
    1098                                         surf_lsm_h%ssws(m) * rmask(j,i,sr) ! w"s"
     1040                      sums_l(nzb,117,tn) = sums_l(nzb,117,tn) +                                    &
     1041                                           surf_lsm_h%ssws(m) * rmask(j,i,sr) ! w"s"
    10991042                   ENDIF
    11001043#endif
    11011044
    11021045                ENDIF
    1103                 IF ( surf_usm_h%end_index(j,i) >=                              &
    1104                      surf_usm_h%start_index(j,i) )  THEN
     1046                IF ( surf_usm_h%end_index(j,i) >= surf_usm_h%start_index(j,i) )  THEN
    11051047                   m = surf_usm_h%start_index(j,i)
    11061048                   !$ACC ATOMIC
    1107                    sums_l(nzb,12,tn) = sums_l(nzb,12,tn) + &
    1108                                     momentumflux_output_conversion(nzb) * &
    1109                                     surf_usm_h%usws(m) * rmask(j,i,sr)     ! w"u"
     1049                   sums_l(nzb,12,tn) = sums_l(nzb,12,tn) +                                         &
     1050                                       momentumflux_output_conversion(nzb) *                      &
     1051                                       surf_usm_h%usws(m) * rmask(j,i,sr)                ! w"u"
    11101052                   !$ACC ATOMIC
    1111                    sums_l(nzb,14,tn) = sums_l(nzb,14,tn) + &
    1112                                     momentumflux_output_conversion(nzb) * &
    1113                                     surf_usm_h%vsws(m) * rmask(j,i,sr)     ! w"v"
     1053                   sums_l(nzb,14,tn) = sums_l(nzb,14,tn) +                                         &
     1054                                       momentumflux_output_conversion(nzb) *                      &
     1055                                       surf_usm_h%vsws(m) * rmask(j,i,sr)                ! w"v"
    11141056                   !$ACC ATOMIC
    1115                    sums_l(nzb,16,tn) = sums_l(nzb,16,tn) + &
    1116                                     heatflux_output_conversion(nzb) * &
    1117                                     surf_usm_h%shf(m)  * rmask(j,i,sr)     ! w"pt"
     1057                   sums_l(nzb,16,tn) = sums_l(nzb,16,tn) +                                         &
     1058                                       heatflux_output_conversion(nzb) *                          &
     1059                                       surf_usm_h%shf(m)  * rmask(j,i,sr)                ! w"pt"
    11181060#if 0
    1119                    sums_l(nzb,58,tn) = sums_l(nzb,58,tn) + &
    1120                                     0.0_wp * rmask(j,i,sr)        ! u"pt"
    1121                    sums_l(nzb,61,tn) = sums_l(nzb,61,tn) + &
    1122                                     0.0_wp * rmask(j,i,sr)        ! v"pt"
     1061                   sums_l(nzb,58,tn) = sums_l(nzb,58,tn) + 0.0_wp * rmask(j,i,sr)        ! u"pt"
     1062                   sums_l(nzb,61,tn) = sums_l(nzb,61,tn) + 0.0_wp * rmask(j,i,sr)        ! v"pt"
    11231063#endif
    11241064#ifndef _OPENACC
    11251065                   IF ( ocean_mode )  THEN
    1126                       sums_l(nzb,65,tn) = sums_l(nzb,65,tn) + &
    1127                                        surf_usm_h%sasws(m) * rmask(j,i,sr)  ! w"sa"
     1066                      sums_l(nzb,65,tn) = sums_l(nzb,65,tn) +                                      &
     1067                                          surf_usm_h%sasws(m) * rmask(j,i,sr)            ! w"sa"
    11281068                   ENDIF
    11291069                   IF ( humidity )  THEN
    1130                       sums_l(nzb,48,tn) = sums_l(nzb,48,tn) +                     &
    1131                                        waterflux_output_conversion(nzb) *      &
    1132                                        surf_usm_h%qsws(m) * rmask(j,i,sr)  ! w"q" (w"qv")
    1133                       sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                   &
    1134                                        ( 1.0_wp + 0.61_wp * q(nzb,j,i) ) *     &
    1135                                        surf_usm_h%shf(m) + 0.61_wp * pt(nzb,j,i) *      &
    1136                                                   surf_usm_h%qsws(m) )                  &
    1137                                        * heatflux_output_conversion(nzb)
     1070                      sums_l(nzb,48,tn) = sums_l(nzb,48,tn) +                                      &
     1071                                          waterflux_output_conversion(nzb) *                       &
     1072                                          surf_usm_h%qsws(m) * rmask(j,i,sr)             ! w"q" (w"qv")
     1073                      sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                                    &
     1074                                          ( 1.0_wp + 0.61_wp * q(nzb,j,i) ) *                      &
     1075                                          surf_usm_h%shf(m) + 0.61_wp * pt(nzb,j,i) *              &
     1076                                          surf_usm_h%qsws(m)  )                                    &
     1077                                          * heatflux_output_conversion(nzb)
    11381078                      IF ( cloud_droplets )  THEN
    1139                          sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                &
    1140                                          ( 1.0_wp + 0.61_wp * q(nzb,j,i) -     &
    1141                                            ql(nzb,j,i) ) * surf_usm_h%shf(m) +          &
    1142                                            0.61_wp * pt(nzb,j,i) * surf_usm_h%qsws(m) ) &
    1143                                           * heatflux_output_conversion(nzb)
     1079                         sums_l(nzb,45,tn) = sums_l(nzb,45,tn) + (                                 &
     1080                                             ( 1.0_wp + 0.61_wp * q(nzb,j,i) -                     &
     1081                                              ql(nzb,j,i) ) * surf_usm_h%shf(m) +                  &
     1082                                              0.61_wp * pt(nzb,j,i) * surf_usm_h%qsws(m) )        &
     1083                                             * heatflux_output_conversion(nzb)
    11441084                      ENDIF
    11451085                      IF ( bulk_cloud_model )  THEN
    11461086!
    11471087!--                      Formula does not work if ql(nzb) /= 0.0
    1148                          sums_l(nzb,51,tn) = sums_l(nzb,51,tn) +                  &
    1149                                           waterflux_output_conversion(nzb) *   &
    1150                                           surf_usm_h%qsws(m) * rmask(j,i,sr) ! w"q" (w"qv")
     1088                         sums_l(nzb,51,tn) = sums_l(nzb,51,tn) +                                   &
     1089                                             waterflux_output_conversion(nzb) *                    &
     1090                                             surf_usm_h%qsws(m) * rmask(j,i,sr)          ! w"q" (w"qv")
    11511091                      ENDIF
    11521092                   ENDIF
    11531093                   IF ( passive_scalar )  THEN
    1154                       sums_l(nzb,117,tn) = sums_l(nzb,117,tn) +                     &
    1155                                         surf_usm_h%ssws(m) * rmask(j,i,sr) ! w"s"
     1094                      sums_l(nzb,117,tn) = sums_l(nzb,117,tn) +                                    &
     1095                                           surf_usm_h%ssws(m) * rmask(j,i,sr)            ! w"s"
    11561096                   ENDIF
    11571097#endif
     
    11631103#ifndef _OPENACC
    11641104             IF ( .NOT. neutral )  THEN
    1165                 IF ( surf_def_h(0)%end_index(j,i) >=                           &
    1166                      surf_def_h(0)%start_index(j,i) )  THEN
     1105                IF ( surf_def_h(0)%end_index(j,i) >= surf_def_h(0)%start_index(j,i) )  THEN
    11671106                   m = surf_def_h(0)%start_index(j,i)
    1168                    sums_l(nzb,112,tn) = sums_l(nzb,112,tn) +                   &
    1169                                         surf_def_h(0)%ol(m)  * rmask(j,i,sr) ! L
    1170                 ENDIF
    1171                 IF ( surf_lsm_h%end_index(j,i) >=                              &
    1172                      surf_lsm_h%start_index(j,i) )  THEN
     1107                   sums_l(nzb,112,tn) = sums_l(nzb,112,tn) + surf_def_h(0)%ol(m) * rmask(j,i,sr) ! L
     1108                ENDIF
     1109                IF ( surf_lsm_h%end_index(j,i) >= surf_lsm_h%start_index(j,i) )  THEN
    11731110                   m = surf_lsm_h%start_index(j,i)
    1174                    sums_l(nzb,112,tn) = sums_l(nzb,112,tn) +                   &
    1175                                         surf_lsm_h%ol(m)  * rmask(j,i,sr) ! L
    1176                 ENDIF
    1177                 IF ( surf_usm_h%end_index(j,i) >=                              &
    1178                      surf_usm_h%start_index(j,i) )  THEN
     1111                   sums_l(nzb,112,tn) = sums_l(nzb,112,tn) + surf_lsm_h%ol(m)    * rmask(j,i,sr) ! L
     1112                ENDIF
     1113                IF ( surf_usm_h%end_index(j,i) >= surf_usm_h%start_index(j,i) )  THEN
    11791114                   m = surf_usm_h%start_index(j,i)
    1180                    sums_l(nzb,112,tn) = sums_l(nzb,112,tn) +                   &
    1181                                         surf_usm_h%ol(m)  * rmask(j,i,sr) ! L
     1115                   sums_l(nzb,112,tn) = sums_l(nzb,112,tn) + surf_usm_h%ol(m)    * rmask(j,i,sr) ! L
    11821116                ENDIF
    11831117             ENDIF
    11841118
    11851119             IF ( radiation )  THEN
    1186                 IF ( surf_def_h(0)%end_index(j,i) >=                           &
    1187                      surf_def_h(0)%start_index(j,i) )  THEN
     1120                IF ( surf_def_h(0)%end_index(j,i) >= surf_def_h(0)%start_index(j,i) )  THEN
    11881121                   m = surf_def_h(0)%start_index(j,i)
    1189                    sums_l(nzb,99,tn)  = sums_l(nzb,99,tn)  +                   &
    1190                                         surf_def_h(0)%rad_net(m) * rmask(j,i,sr)
    1191                    sums_l(nzb,100,tn) = sums_l(nzb,100,tn)  +                  &
    1192                                         surf_def_h(0)%rad_lw_in(m) * rmask(j,i,sr)
    1193                    sums_l(nzb,101,tn) = sums_l(nzb,101,tn)  +                  &
     1122                   sums_l(nzb,99,tn)  = sums_l(nzb,99,tn)   +                                      &
     1123                                        surf_def_h(0)%rad_net(m)    * rmask(j,i,sr)
     1124                   sums_l(nzb,100,tn) = sums_l(nzb,100,tn)  +                                      &
     1125                                        surf_def_h(0)%rad_lw_in(m)  * rmask(j,i,sr)
     1126                   sums_l(nzb,101,tn) = sums_l(nzb,101,tn)  +                                      &
    11941127                                        surf_def_h(0)%rad_lw_out(m) * rmask(j,i,sr)
    1195                    sums_l(nzb,102,tn) = sums_l(nzb,102,tn)  +                  &
    1196                                         surf_def_h(0)%rad_sw_in(m) * rmask(j,i,sr)
    1197                    sums_l(nzb,103,tn) = sums_l(nzb,103,tn)  +                  &
     1128                   sums_l(nzb,102,tn) = sums_l(nzb,102,tn)  +                                      &
     1129                                        surf_def_h(0)%rad_sw_in(m)  * rmask(j,i,sr)
     1130                   sums_l(nzb,103,tn) = sums_l(nzb,103,tn)  +                                      &
    11981131                                        surf_def_h(0)%rad_sw_out(m) * rmask(j,i,sr)
    11991132                ENDIF
    1200                 IF ( surf_lsm_h%end_index(j,i) >=                              &
    1201                      surf_lsm_h%start_index(j,i) )  THEN
     1133                IF ( surf_lsm_h%end_index(j,i) >= surf_lsm_h%start_index(j,i) )  THEN
    12021134                   m = surf_lsm_h%start_index(j,i)
    1203                    sums_l(nzb,99,tn)  = sums_l(nzb,99,tn)  +                   &
    1204                                         surf_lsm_h%rad_net(m) * rmask(j,i,sr)
    1205                    sums_l(nzb,100,tn) = sums_l(nzb,100,tn)  +                  &
    1206                                         surf_lsm_h%rad_lw_in(m) * rmask(j,i,sr)
    1207                    sums_l(nzb,101,tn) = sums_l(nzb,101,tn)  +                  &
     1135                   sums_l(nzb,99,tn)  = sums_l(nzb,99,tn)   +                                      &
     1136                                        surf_lsm_h%rad_net(m)    * rmask(j,i,sr)
     1137                   sums_l(nzb,100,tn) = sums_l(nzb,100,tn)  +                                      &
     1138                                        surf_lsm_h%rad_lw_in(m)  * rmask(j,i,sr)
     1139                   sums_l(nzb,101,tn) = sums_l(nzb,101,tn)  +                                      &
    12081140                                        surf_lsm_h%rad_lw_out(m) * rmask(j,i,sr)
    1209                    sums_l(nzb,102,tn) = sums_l(nzb,102,tn)  +                  &
    1210                                         surf_lsm_h%rad_sw_in(m) * rmask(j,i,sr)
    1211                    sums_l(nzb,103,tn) = sums_l(nzb,103,tn)  +                  &
     1141                   sums_l(nzb,102,tn) = sums_l(nzb,102,tn)  +                                      &
     1142                                        surf_lsm_h%rad_sw_in(m)  * rmask(j,i,sr)
     1143                   sums_l(nzb,103,tn) = sums_l(nzb,103,tn)  +                                      &
    12121144                                        surf_lsm_h%rad_sw_out(m) * rmask(j,i,sr)
    12131145                ENDIF
    1214                 IF ( surf_usm_h%end_index(j,i) >=                              &
    1215                      surf_usm_h%start_index(j,i) )  THEN
     1146                IF ( surf_usm_h%end_index(j,i) >= surf_usm_h%start_index(j,i) )  THEN
    12161147                   m = surf_usm_h%start_index(j,i)
    1217                    sums_l(nzb,99,tn)  = sums_l(nzb,99,tn)  +                   &
    1218                                         surf_usm_h%rad_net(m) * rmask(j,i,sr)
    1219                    sums_l(nzb,100,tn) = sums_l(nzb,100,tn)  +                  &
    1220                                         surf_usm_h%rad_lw_in(m) * rmask(j,i,sr)
    1221                    sums_l(nzb,101,tn) = sums_l(nzb,101,tn)  +                  &
     1148                   sums_l(nzb,99,tn)  = sums_l(nzb,99,tn)   +                                      &
     1149                                        surf_usm_h%rad_net(m)    * rmask(j,i,sr)
     1150                   sums_l(nzb,100,tn) = sums_l(nzb,100,tn)  +                                      &
     1151                                        surf_usm_h%rad_lw_in(m)  * rmask(j,i,sr)
     1152                   sums_l(nzb,101,tn) = sums_l(nzb,101,tn)  +                                      &
    12221153                                        surf_usm_h%rad_lw_out(m) * rmask(j,i,sr)
    1223                    sums_l(nzb,102,tn) = sums_l(nzb,102,tn)  +                  &
    1224                                         surf_usm_h%rad_sw_in(m) * rmask(j,i,sr)
    1225                    sums_l(nzb,103,tn) = sums_l(nzb,103,tn)  +                  &
     1154                   sums_l(nzb,102,tn) = sums_l(nzb,102,tn)  +                                      &
     1155                                        surf_usm_h%rad_sw_in(m)  * rmask(j,i,sr)
     1156                   sums_l(nzb,103,tn) = sums_l(nzb,103,tn)  +                                      &
    12261157                                        surf_usm_h%rad_sw_out(m) * rmask(j,i,sr)
    12271158                ENDIF
     
    12301161                IF ( radiation_scheme == 'rrtmg' )  THEN
    12311162
    1232                    IF ( surf_def_h(0)%end_index(j,i) >=                        &
    1233                         surf_def_h(0)%start_index(j,i) )  THEN
     1163                   IF ( surf_def_h(0)%end_index(j,i) >= surf_def_h(0)%start_index(j,i) )  THEN
    12341164                      m = surf_def_h(0)%start_index(j,i)
    1235                       sums_l(nzb,108,tn)  = sums_l(nzb,108,tn)  +              &
    1236                                    surf_def_h(0)%rrtm_aldif(m,0) * rmask(j,i,sr)
    1237                       sums_l(nzb,109,tn) = sums_l(nzb,109,tn)  +               &
    1238                                    surf_def_h(0)%rrtm_aldir(m,0) * rmask(j,i,sr)
    1239                       sums_l(nzb,110,tn) = sums_l(nzb,110,tn)  +               &
    1240                                    surf_def_h(0)%rrtm_asdif(m,0) * rmask(j,i,sr)
    1241                       sums_l(nzb,111,tn) = sums_l(nzb,111,tn)  +               &
    1242                                    surf_def_h(0)%rrtm_asdir(m,0) * rmask(j,i,sr)
     1165                      sums_l(nzb,108,tn)  = sums_l(nzb,108,tn)  +                                  &
     1166                                            surf_def_h(0)%rrtm_aldif(m,0) * rmask(j,i,sr)
     1167                      sums_l(nzb,109,tn) = sums_l(nzb,109,tn)  +                                   &
     1168                                           surf_def_h(0)%rrtm_aldir(m,0) * rmask(j,i,sr)
     1169                      sums_l(nzb,110,tn) = sums_l(nzb,110,tn)  +                                   &
     1170                                           surf_def_h(0)%rrtm_asdif(m,0) * rmask(j,i,sr)
     1171                      sums_l(nzb,111,tn) = sums_l(nzb,111,tn)  +                                   &
     1172                                           surf_def_h(0)%rrtm_asdir(m,0) * rmask(j,i,sr)
    12431173                   ENDIF
    1244                    IF ( surf_lsm_h%end_index(j,i) >=                           &
    1245                         surf_lsm_h%start_index(j,i) )  THEN
     1174                   IF ( surf_lsm_h%end_index(j,i) >= surf_lsm_h%start_index(j,i) )  THEN
    12461175                      m = surf_lsm_h%start_index(j,i)
    1247                       sums_l(nzb,108,tn)  = sums_l(nzb,108,tn)  +              &
    1248                                SUM( surf_lsm_h%frac(m,:) *                     &
    1249                                     surf_lsm_h%rrtm_aldif(m,:) ) * rmask(j,i,sr)
    1250                       sums_l(nzb,109,tn) = sums_l(nzb,109,tn)  +               &
    1251                                SUM( surf_lsm_h%frac(m,:) *                     &
    1252                                     surf_lsm_h%rrtm_aldir(m,:) ) * rmask(j,i,sr)
    1253                       sums_l(nzb,110,tn) = sums_l(nzb,110,tn)  +               &
    1254                                SUM( surf_lsm_h%frac(m,:) *                     &
    1255                                     surf_lsm_h%rrtm_asdif(m,:) ) * rmask(j,i,sr)
    1256                       sums_l(nzb,111,tn) = sums_l(nzb,111,tn)  +               &
    1257                                SUM( surf_lsm_h%frac(m,:) *                     &
    1258                                     surf_lsm_h%rrtm_asdir(m,:) ) * rmask(j,i,sr)
     1176                      sums_l(nzb,108,tn)  = sums_l(nzb,108,tn)  +                                  &
     1177                                            SUM( surf_lsm_h%frac(m,:) *                            &
     1178                                                 surf_lsm_h%rrtm_aldif(m,:) ) * rmask(j,i,sr)
     1179                      sums_l(nzb,109,tn) = sums_l(nzb,109,tn)  +                                   &
     1180                                           SUM( surf_lsm_h%frac(m,:) *                             &
     1181                                                surf_lsm_h%rrtm_aldir(m,:) ) * rmask(j,i,sr)
     1182                      sums_l(nzb,110,tn) = sums_l(nzb,110,tn)  +                                   &
     1183                                           SUM( surf_lsm_h%frac(m,:) *                             &
     1184                                                surf_lsm_h%rrtm_asdif(m,:) ) * rmask(j,i,sr)
     1185                      sums_l(nzb,111,tn) = sums_l(nzb,111,tn)  +                                   &
     1186                                           SUM( surf_lsm_h%frac(m,:) *                             &
     1187                                                surf_lsm_h%rrtm_asdir(m,:) ) * rmask(j,i,sr)
    12591188                   ENDIF
    1260                    IF ( surf_usm_h%end_index(j,i) >=                           &
    1261                         surf_usm_h%start_index(j,i) )  THEN
     1189                   IF ( surf_usm_h%end_index(j,i) >= surf_usm_h%start_index(j,i) )  THEN
    12621190                      m = surf_usm_h%start_index(j,i)
    1263                       sums_l(nzb,108,tn)  = sums_l(nzb,108,tn)  +              &
    1264                                SUM( surf_usm_h%frac(m,:) *                     &
    1265                                     surf_usm_h%rrtm_aldif(m,:) ) * rmask(j,i,sr)
    1266                       sums_l(nzb,109,tn) = sums_l(nzb,109,tn)  +               &
    1267                                SUM( surf_usm_h%frac(m,:) *                     &
    1268                                     surf_usm_h%rrtm_aldir(m,:) ) * rmask(j,i,sr)
    1269                       sums_l(nzb,110,tn) = sums_l(nzb,110,tn)  +               &
    1270                                SUM( surf_usm_h%frac(m,:) *                     &
    1271                                     surf_usm_h%rrtm_asdif(m,:) ) * rmask(j,i,sr)
    1272                       sums_l(nzb,111,tn) = sums_l(nzb,111,tn)  +               &
    1273                                SUM( surf_usm_h%frac(m,:) *                     &
    1274                                     surf_usm_h%rrtm_asdir(m,:) ) * rmask(j,i,sr)
     1191                      sums_l(nzb,108,tn)  = sums_l(nzb,108,tn)  +                                  &
     1192                                            SUM( surf_usm_h%frac(m,:) *                            &
     1193                                                 surf_usm_h%rrtm_aldif(m,:) ) * rmask(j,i,sr)
     1194                      sums_l(nzb,109,tn) = sums_l(nzb,109,tn)  +                                   &
     1195                                           SUM( surf_usm_h%frac(m,:) *                             &
     1196                                                surf_usm_h%rrtm_aldir(m,:) ) * rmask(j,i,sr)
     1197                      sums_l(nzb,110,tn) = sums_l(nzb,110,tn)  +                                   &
     1198                                           SUM( surf_usm_h%frac(m,:) *                             &
     1199                                                surf_usm_h%rrtm_asdif(m,:) ) * rmask(j,i,sr)
     1200                      sums_l(nzb,111,tn) = sums_l(nzb,111,tn)  +                                   &
     1201                                           SUM( surf_usm_h%frac(m,:) *                             &
     1202                                                surf_usm_h%rrtm_asdir(m,:) ) * rmask(j,i,sr)
    12751203                   ENDIF
    12761204
     
    12841212                m = surf_def_h(2)%start_index(j,i)
    12851213                !$ACC ATOMIC
    1286                 sums_l(nzt,12,tn) = sums_l(nzt,12,tn) + &
    1287                                     momentumflux_output_conversion(nzt) * &
     1214                sums_l(nzt,12,tn) = sums_l(nzt,12,tn) +                                            &
     1215                                    momentumflux_output_conversion(nzt) *                          &
    12881216                                    surf_def_h(2)%usws(m) * rmask(j,i,sr)    ! w"u"
    12891217                !$ACC ATOMIC
    1290                 sums_l(nzt+1,12,tn) = sums_l(nzt+1,12,tn) + &
    1291                                     momentumflux_output_conversion(nzt+1) * &
    1292                                     surf_def_h(2)%usws(m) * rmask(j,i,sr)    ! w"u"
    1293                 !$ACC ATOMIC
    1294                 sums_l(nzt,14,tn) = sums_l(nzt,14,tn) + &
    1295                                     momentumflux_output_conversion(nzt) * &
     1218                sums_l(nzt+1,12,tn) = sums_l(nzt+1,12,tn) +                                        &
     1219                                      momentumflux_output_conversion(nzt+1) *                      &
     1220                                      surf_def_h(2)%usws(m) * rmask(j,i,sr)  ! w"u"
     1221                !$ACC ATOMIC
     1222                sums_l(nzt,14,tn) = sums_l(nzt,14,tn) +                                            &
     1223                                    momentumflux_output_conversion(nzt) *                          &
    12961224                                    surf_def_h(2)%vsws(m) * rmask(j,i,sr)    ! w"v"
    12971225                !$ACC ATOMIC
    1298                 sums_l(nzt+1,14,tn) = sums_l(nzt+1,14,tn) + &
    1299                                     momentumflux_output_conversion(nzt+1) * &
    1300                                     surf_def_h(2)%vsws(m) * rmask(j,i,sr)    ! w"v"
    1301                 !$ACC ATOMIC
    1302                 sums_l(nzt,16,tn) = sums_l(nzt,16,tn) + &
    1303                                     heatflux_output_conversion(nzt) * &
    1304                                     surf_def_h(2)%shf(m)  * rmask(j,i,sr)   ! w"pt"
    1305                 !$ACC ATOMIC
    1306                 sums_l(nzt+1,16,tn) = sums_l(nzt+1,16,tn) + &
    1307                                     heatflux_output_conversion(nzt+1) * &
    1308                                     surf_def_h(2)%shf(m)  * rmask(j,i,sr)   ! w"pt"
     1226                sums_l(nzt+1,14,tn) = sums_l(nzt+1,14,tn) +                                        &
     1227                                      momentumflux_output_conversion(nzt+1) *                      &
     1228                                      surf_def_h(2)%vsws(m) * rmask(j,i,sr)  ! w"v"
     1229                !$ACC ATOMIC
     1230                sums_l(nzt,16,tn) = sums_l(nzt,16,tn) +                                            &
     1231                                    heatflux_output_conversion(nzt) *                              &
     1232                                    surf_def_h(2)%shf(m)  * rmask(j,i,sr)    ! w"pt"
     1233                !$ACC ATOMIC
     1234                sums_l(nzt+1,16,tn) = sums_l(nzt+1,16,tn) +                                        &
     1235                                      heatflux_output_conversion(nzt+1) *                          &
     1236                                      surf_def_h(2)%shf(m)  * rmask(j,i,sr)  ! w"pt"
    13091237#if 0
    1310                 sums_l(nzt:nzt+1,58,tn) = sums_l(nzt:nzt+1,58,tn) + &
    1311                                     0.0_wp * rmask(j,i,sr)        ! u"pt"
    1312                 sums_l(nzt:nzt+1,61,tn) = sums_l(nzt:nzt+1,61,tn) + &
    1313                                     0.0_wp * rmask(j,i,sr)        ! v"pt"
     1238                sums_l(nzt:nzt+1,58,tn) = sums_l(nzt:nzt+1,58,tn) +                                &
     1239                                          0.0_wp * rmask(j,i,sr)             ! u"pt"
     1240                sums_l(nzt:nzt+1,61,tn) = sums_l(nzt:nzt+1,61,tn) +                                &
     1241                                          0.0_wp * rmask(j,i,sr)             ! v"pt"
    13141242#endif
    13151243#ifndef _OPENACC
     
    13191247                ENDIF
    13201248                IF ( humidity )  THEN
    1321                    sums_l(nzt,48,tn) = sums_l(nzt,48,tn) +                     &
    1322                                        waterflux_output_conversion(nzt) *      &
     1249                   sums_l(nzt,48,tn) = sums_l(nzt,48,tn) +                                         &
     1250                                       waterflux_output_conversion(nzt) *                          &
    13231251                                       surf_def_h(2)%qsws(m) * rmask(j,i,sr) ! w"q" (w"qv")
    1324                    sums_l(nzt,45,tn) = sums_l(nzt,45,tn) + (                   &
    1325                                        ( 1.0_wp + 0.61_wp * q(nzt,j,i) ) *     &
    1326                                        surf_def_h(2)%shf(m) +                  &
    1327                                        0.61_wp * pt(nzt,j,i) *    &
    1328                                        surf_def_h(2)%qsws(m) )      &
     1252                   sums_l(nzt,45,tn) = sums_l(nzt,45,tn) +   (                                     &
     1253                                       ( 1.0_wp + 0.61_wp * q(nzt,j,i) ) *                         &
     1254                                       surf_def_h(2)%shf(m) +                                      &
     1255                                       0.61_wp * pt(nzt,j,i) *                                     &
     1256                                       surf_def_h(2)%qsws(m) )                                     &
    13291257                                       * heatflux_output_conversion(nzt)
    13301258                   IF ( cloud_droplets )  THEN
    1331                       sums_l(nzt,45,tn) = sums_l(nzt,45,tn) + (                &
    1332                                           ( 1.0_wp + 0.61_wp * q(nzt,j,i) -    &
    1333                                             ql(nzt,j,i) ) *                    &
    1334                                             surf_def_h(2)%shf(m) +             &
    1335                                            0.61_wp * pt(nzt,j,i) *             &
    1336                                            surf_def_h(2)%qsws(m) )&
     1259                      sums_l(nzt,45,tn) = sums_l(nzt,45,tn) +    (                                 &
     1260                                          ( 1.0_wp + 0.61_wp * q(nzt,j,i) -                        &
     1261                                            ql(nzt,j,i) ) *                                        &
     1262                                            surf_def_h(2)%shf(m) +                                 &
     1263                                           0.61_wp * pt(nzt,j,i) *                                 &
     1264                                           surf_def_h(2)%qsws(m) )                                 &
    13371265                                           * heatflux_output_conversion(nzt)
    13381266                   ENDIF
     
    13401268!
    13411269!--                   Formula does not work if ql(nzb) /= 0.0
    1342                       sums_l(nzt,51,tn) = sums_l(nzt,51,tn) + &   ! w"q" (w"qv")
    1343                                           waterflux_output_conversion(nzt) *   &
     1270                      sums_l(nzt,51,tn) = sums_l(nzt,51,tn) +              &  ! w"q" (w"qv")
     1271                                          waterflux_output_conversion(nzt) *                       &
    13441272                                          surf_def_h(2)%qsws(m) * rmask(j,i,sr)
    13451273                   ENDIF
    13461274                ENDIF
    13471275                IF ( passive_scalar )  THEN
    1348                    sums_l(nzt,117,tn) = sums_l(nzt,117,tn) + &
     1276                   sums_l(nzt,117,tn) = sums_l(nzt,117,tn) +                                       &
    13491277                                        surf_def_h(2)%ssws(m) * rmask(j,i,sr) ! w"s"
    13501278                ENDIF
     
    13541282!
    13551283!--          Resolved fluxes (can be computed for all horizontal points)
    1356 !--          NOTE: for simplicity, nzb_s_inner is used below, although strictly
    1357 !--          ----  speaking the following k-loop would have to be split up and
    1358 !--                rearranged according to the staggered grid.
     1284!--          NOTE: for simplicity, nzb_s_inner is used below, although strictly speaking the
     1285!--          ----  following k-loop would have to be split up and rearranged according to the
     1286!--                staggered grid.
    13591287             DO  k = nzb, nzt
    13601288                flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 22 ) )
    1361                 ust = 0.5_wp * ( u(k,j,i)   - hom(k,1,1,sr) +                  &
     1289                ust = 0.5_wp * ( u(k,j,i)   - hom(k,1,1,sr) +                                      &
    13621290                                 u(k+1,j,i) - hom(k+1,1,1,sr) )
    1363                 vst = 0.5_wp * ( v(k,j,i)   - hom(k,1,2,sr) +                  &
     1291                vst = 0.5_wp * ( v(k,j,i)   - hom(k,1,2,sr) +                                      &
    13641292                                 v(k+1,j,i) - hom(k+1,1,2,sr) )
    1365                 pts = 0.5_wp * ( pt(k,j,i)   - hom(k,1,4,sr) +                 &
     1293                pts = 0.5_wp * ( pt(k,j,i)   - hom(k,1,4,sr) +                                     &
    13661294                                 pt(k+1,j,i) - hom(k+1,1,4,sr) )
    1367 
     1295!
    13681296!--             Higher moments
    13691297                !$ACC ATOMIC
    1370                 sums_l(k,35,tn) = sums_l(k,35,tn) + pts * w(k,j,i)**2 *        &
    1371                                                     rmask(j,i,sr) * flag
    1372                 !$ACC ATOMIC
    1373                 sums_l(k,36,tn) = sums_l(k,36,tn) + pts**2 * w(k,j,i) *        &
    1374                                                     rmask(j,i,sr) * flag
    1375 
    1376 !
    1377 !--             Salinity flux and density (density does not belong to here,
    1378 !--             but so far there is no other suitable place to calculate)
     1298                sums_l(k,35,tn) = sums_l(k,35,tn) + pts * w(k,j,i)**2 * rmask(j,i,sr) * flag
     1299                !$ACC ATOMIC
     1300                sums_l(k,36,tn) = sums_l(k,36,tn) + pts**2 * w(k,j,i) * rmask(j,i,sr) * flag
     1301
     1302!
     1303!--             Salinity flux and density (density does not belong to here, but so far there is no
     1304!--             other suitable place to calculate)
    13791305#ifndef _OPENACC
    13801306                IF ( ocean_mode )  THEN
    13811307                   IF( .NOT. ws_scheme_sca .OR. sr /= 0 )  THEN
    1382                       pts = 0.5_wp * ( sa(k,j,i)   - hom(k,1,23,sr) +          &
     1308                      pts = 0.5_wp * ( sa(k,j,i)   - hom(k,1,23,sr) +                              &
    13831309                                       sa(k+1,j,i) - hom(k+1,1,23,sr) )
    1384                       sums_l(k,66,tn) = sums_l(k,66,tn) + pts * w(k,j,i) *     &
     1310                      sums_l(k,66,tn) = sums_l(k,66,tn) + pts * w(k,j,i) *                         &
    13851311                                        rmask(j,i,sr) * flag
    13861312                   ENDIF
    1387                    sums_l(k,64,tn) = sums_l(k,64,tn) + rho_ocean(k,j,i) *      &
    1388                                                        rmask(j,i,sr) * flag
    1389                    sums_l(k,71,tn) = sums_l(k,71,tn) + prho(k,j,i) *           &
    1390                                                        rmask(j,i,sr) * flag
    1391                 ENDIF
    1392 
    1393 !
    1394 !--             Buoyancy flux, water flux, humidity flux, liquid water
    1395 !--             content, rain drop concentration and rain water content
     1313                   sums_l(k,64,tn) = sums_l(k,64,tn) + rho_ocean(k,j,i) * rmask(j,i,sr) * flag
     1314                   sums_l(k,71,tn) = sums_l(k,71,tn) + prho(k,j,i)      * rmask(j,i,sr) * flag
     1315                ENDIF
     1316
     1317!
     1318!--             Buoyancy flux, water flux, humidity flux, liquid water content, rain drop
     1319!--             concentration and rain water content
    13961320                IF ( humidity )  THEN
    1397                    IF ( bulk_cloud_model .OR. cloud_droplets )  THEN
    1398                       pts = 0.5_wp * ( vpt(k,j,i)   - hom(k,1,44,sr) +         &
    1399                                     vpt(k+1,j,i) - hom(k+1,1,44,sr) )
    1400                       sums_l(k,46,tn) = sums_l(k,46,tn) + pts * w(k,j,i) *     &
    1401                                                rho_air_zw(k) *                 &
    1402                                                heatflux_output_conversion(k) * &
     1321                   IF ( bulk_cloud_model  .OR. cloud_droplets )  THEN
     1322                      pts = 0.5_wp * ( vpt(k,j,i)   - hom(k,1,44,sr) +                             &
     1323                                       vpt(k+1,j,i) - hom(k+1,1,44,sr) )
     1324                      sums_l(k,46,tn) = sums_l(k,46,tn) + pts * w(k,j,i) *                         &
     1325                                                          rho_air_zw(k) *                          &
     1326                                                          heatflux_output_conversion(k) *          &
    14031327                                                          rmask(j,i,sr) * flag
    1404                       sums_l(k,54,tn) = sums_l(k,54,tn) + ql(k,j,i) * rmask(j,i,sr) &
    1405                                                                     * flag
     1328                      sums_l(k,54,tn) = sums_l(k,54,tn) + ql(k,j,i) * rmask(j,i,sr) * flag
    14061329
    14071330                      IF ( .NOT. cloud_droplets )  THEN
    1408                          pts = 0.5_wp *                                        &
    1409                               ( ( q(k,j,i) - ql(k,j,i) ) -                     &
    1410                               hom(k,1,42,sr) +                                 &
    1411                               ( q(k+1,j,i) - ql(k+1,j,i) ) -                   &
    1412                               hom(k+1,1,42,sr) )
    1413                          sums_l(k,52,tn) = sums_l(k,52,tn) + pts * w(k,j,i) *  &
    1414                                              rho_air_zw(k) *                   &
    1415                                              waterflux_output_conversion(k) *  &
    1416                                                              rmask(j,i,sr)  *  &
    1417                                                              flag
    1418                          sums_l(k,75,tn) = sums_l(k,75,tn) + qc(k,j,i) *       &
    1419                                                              rmask(j,i,sr) *   &
    1420                                                              flag
    1421                          sums_l(k,76,tn) = sums_l(k,76,tn) + prr(k,j,i) *      &
    1422                                                              rmask(j,i,sr) *   &
    1423                                                              flag
     1331                         pts = 0.5_wp *                                                            &
     1332                               ( ( q(k,j,i) - ql(k,j,i) ) -                                        &
     1333                               hom(k,1,42,sr) +                                                    &
     1334                               ( q(k+1,j,i) - ql(k+1,j,i) ) -                                      &
     1335                               hom(k+1,1,42,sr) )
     1336                         sums_l(k,52,tn) = sums_l(k,52,tn) + pts * w(k,j,i) *                      &
     1337                                             rho_air_zw(k) *                                       &
     1338                                             waterflux_output_conversion(k) *                      &
     1339                                             rmask(j,i,sr) * flag
     1340                         sums_l(k,75,tn) = sums_l(k,75,tn) + qc(k,j,i)  * rmask(j,i,sr) * flag
     1341                         sums_l(k,76,tn) = sums_l(k,76,tn) + prr(k,j,i) * rmask(j,i,sr) * flag
    14241342                         IF ( microphysics_morrison )  THEN
    1425                             sums_l(k,123,tn) = sums_l(k,123,tn) + nc(k,j,i) *  &
    1426                                                                 rmask(j,i,sr) *&
    1427                                                                 flag
     1343                            sums_l(k,123,tn) = sums_l(k,123,tn) + nc(k,j,i) * rmask(j,i,sr) * flag
    14281344                         ENDIF
    14291345                         IF ( microphysics_ice_phase )  THEN
    1430                             sums_l(k,124,tn) = sums_l(k,124,tn) + ni(k,j,i) *  &
    1431                                                                 rmask(j,i,sr) *&
    1432                                                                 flag
    1433                             sums_l(k,125,tn) = sums_l(k,125,tn) + qi(k,j,i) *  &
    1434                                                                 rmask(j,i,sr) *&
    1435                                                                 flag
     1346                            sums_l(k,124,tn) = sums_l(k,124,tn) + ni(k,j,i) * rmask(j,i,sr) * flag
     1347                            sums_l(k,125,tn) = sums_l(k,125,tn) + qi(k,j,i) * rmask(j,i,sr) * flag
    14361348                         ENDIF
    14371349
    14381350                         IF ( microphysics_seifert )  THEN
    1439                             sums_l(k,73,tn) = sums_l(k,73,tn) + nr(k,j,i) *    &
    1440                                                                 rmask(j,i,sr) *&
    1441                                                                 flag
    1442                             sums_l(k,74,tn) = sums_l(k,74,tn) + qr(k,j,i) *    &
    1443                                                                 rmask(j,i,sr) *&
    1444                                                                 flag
     1351                            sums_l(k,73,tn) = sums_l(k,73,tn) + nr(k,j,i) * rmask(j,i,sr) * flag
     1352                            sums_l(k,74,tn) = sums_l(k,74,tn) + qr(k,j,i) * rmask(j,i,sr) * flag
    14451353                         ENDIF
    14461354                      ENDIF
    14471355
    14481356                   ELSE
    1449                       IF( .NOT. ws_scheme_sca .OR. sr /= 0 )  THEN
    1450                          pts = 0.5_wp * ( vpt(k,j,i)   - hom(k,1,44,sr) +      &
     1357                      IF( .NOT. ws_scheme_sca  .OR. sr /= 0 )  THEN
     1358                         pts = 0.5_wp * ( vpt(k,j,i)   - hom(k,1,44,sr) +                          &
    14511359                                          vpt(k+1,j,i) - hom(k+1,1,44,sr) )
    1452                          sums_l(k,46,tn) = sums_l(k,46,tn) + pts * w(k,j,i) *  &
    1453                                               rho_air_zw(k) *                  &
    1454                                               heatflux_output_conversion(k) *  &
    1455                                                              rmask(j,i,sr)  *  &
    1456                                                              flag
    1457                       ELSE IF ( ws_scheme_sca .AND. sr == 0 )  THEN
    1458                          sums_l(k,46,tn) = ( ( 1.0_wp + 0.61_wp *              &
    1459                                                hom(k,1,41,sr) ) *              &
    1460                                              sums_l(k,17,tn) +                 &
    1461                                              0.61_wp * hom(k,1,4,sr) *         &
    1462                                              sums_l(k,49,tn)                   &
    1463                                            ) * heatflux_output_conversion(k) * &
    1464                                                flag
     1360                         sums_l(k,46,tn) = sums_l(k,46,tn) + pts * w(k,j,i) *                      &
     1361                                                             rho_air_zw(k)  *                      &
     1362                                                             heatflux_output_conversion(k) *       &
     1363                                                             rmask(j,i,sr)  * flag
     1364                      ELSE IF ( ws_scheme_sca  .AND.  sr == 0 )  THEN
     1365                         sums_l(k,46,tn) = ( ( 1.0_wp + 0.61_wp *                                  &
     1366                                               hom(k,1,41,sr) ) *                                  &
     1367                                             sums_l(k,17,tn) +                                     &
     1368                                             0.61_wp * hom(k,1,4,sr) *                             &
     1369                                             sums_l(k,49,tn)                                       &
     1370                                           ) * heatflux_output_conversion(k) * flag
    14651371                      END IF
    14661372                   END IF
     
    14681374!
    14691375!--             Passive scalar flux
    1470                 IF ( passive_scalar .AND. ( .NOT. ws_scheme_sca                &
    1471                      .OR. sr /= 0 ) )  THEN
    1472                    pts = 0.5_wp * ( s(k,j,i)   - hom(k,1,115,sr) +             &
     1376                IF ( passive_scalar  .AND.  ( .NOT. ws_scheme_sca .OR. sr /= 0 ) )  THEN
     1377                   pts = 0.5_wp * ( s(k,j,i)   - hom(k,1,115,sr) +                                 &
    14731378                                    s(k+1,j,i) - hom(k+1,1,115,sr) )
    1474                    sums_l(k,114,tn) = sums_l(k,114,tn) + pts * w(k,j,i) *      &
    1475                                                        rmask(j,i,sr) * flag
     1379                   sums_l(k,114,tn) = sums_l(k,114,tn) + pts * w(k,j,i) * rmask(j,i,sr) * flag
    14761380                ENDIF
    14771381#endif
     
    14811385!--             has to be adjusted
    14821386                !$ACC ATOMIC
    1483                 sums_l(k,37,tn) = sums_l(k,37,tn) + w(k,j,i) * 0.5_wp *        &
    1484                                              ( ust**2 + vst**2 + w(k,j,i)**2 ) &
    1485                                            * rho_air_zw(k)                     &
    1486                                            * momentumflux_output_conversion(k) &
    1487                                            * rmask(j,i,sr) * flag
     1387                sums_l(k,37,tn) = sums_l(k,37,tn) + w(k,j,i) * 0.5_wp *                            &
     1388                                                    ( ust**2 + vst**2 + w(k,j,i)**2 )              &
     1389                                                    * rho_air_zw(k)                                &
     1390                                                    * momentumflux_output_conversion(k)            &
     1391                                                    * rmask(j,i,sr) * flag
    14881392             ENDDO
    14891393          ENDDO
     
    15051409             j = surf_lsm_h%j(m)
    15061410
    1507              IF ( i >= nxl  .AND.  i <= nxr  .AND.                             &
    1508                   j >= nys  .AND.  j <= nyn )  THEN
     1411             IF ( i >= nxl  .AND.  i <= nxr  .AND.  j >= nys  .AND.  j <= nyn )  THEN
    15091412                sums_l(nzb,93,tn)  = sums_l(nzb,93,tn) + surf_lsm_h%ghf(m)       * rmask(j,i,sr)
    15101413                sums_l(nzb,94,tn)  = sums_l(nzb,94,tn) + surf_lsm_h%qsws_liq(m)  * rmask(j,i,sr)
     
    15261429             j = surf_lsm_h%j(m)
    15271430
    1528              IF ( i >= nxl  .AND.  i <= nxr  .AND.                             &
    1529                   j >= nys  .AND.  j <= nyn )  THEN
     1431             IF ( i >= nxl  .AND.  i <= nxr  .AND.  j >= nys  .AND.  j <= nyn )  THEN
    15301432
    15311433                DO  k = nzb_soil, nzt_soil
    1532                    sums_l(k,89,tn)  = sums_l(k,89,tn)  + t_soil_h%var_2d(k,m)  &
    1533                                       * rmask(j,i,sr)
    1534                    sums_l(k,91,tn)  = sums_l(k,91,tn)  + m_soil_h%var_2d(k,m)  &
    1535                                       * rmask(j,i,sr)
     1434                   sums_l(k,89,tn)  = sums_l(k,89,tn)  + t_soil_h%var_2d(k,m) * rmask(j,i,sr)
     1435                   sums_l(k,91,tn)  = sums_l(k,91,tn)  + m_soil_h%var_2d(k,m) * rmask(j,i,sr)
    15361436                ENDDO
    15371437             ENDIF
     
    15401440       ENDIF
    15411441!
    1542 !--    For speed optimization fluxes which have been computed in part directly
    1543 !--    inside the WS advection routines are treated seperatly
     1442!--    For speed optimization fluxes which have been computed in part directly inside the WS
     1443!--    advection routines are treated seperatly.
    15441444!--    Momentum fluxes first:
    15451445
     
    15531453                DO  k = nzb, nzt
    15541454!
    1555 !--                Flag 23 is used to mask surface fluxes as well as model-top
    1556 !--                fluxes, which are added further below.
    1557                    flag = MERGE( 1.0_wp, 0.0_wp,                               &
    1558                                  BTEST( wall_flags_total_0(k,j,i), 23 ) ) *    &
    1559                           MERGE( 1.0_wp, 0.0_wp,                               &
    1560                                  BTEST( wall_flags_total_0(k,j,i), 9  ) )
    1561 
    1562                    ust = 0.5_wp * ( u(k,j,i)   - hom(k,1,1,sr) +               &
     1455!--                Flag 23 is used to mask surface fluxes as well as model-top fluxes, which are
     1456!--                added further below.
     1457                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 23 ) ) *        &
     1458                          MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 9  ) )
     1459
     1460                   ust = 0.5_wp * ( u(k,j,i)   - hom(k,1,1,sr) +                                   &
    15631461                                    u(k+1,j,i) - hom(k+1,1,1,sr) )
    1564                    vst = 0.5_wp * ( v(k,j,i)   - hom(k,1,2,sr) +               &
     1462                   vst = 0.5_wp * ( v(k,j,i)   - hom(k,1,2,sr) +                                   &
    15651463                                    v(k+1,j,i) - hom(k+1,1,2,sr) )
    15661464!
    15671465!--                Momentum flux w*u*
    1568                    sums_l(k,13,tn) = sums_l(k,13,tn) + 0.5_wp *                &
    1569                                                      ( w(k,j,i-1) + w(k,j,i) ) &
    1570                                            * rho_air_zw(k)                     &
    1571                                            * momentumflux_output_conversion(k) &
    1572                                                      * ust * rmask(j,i,sr)     &
     1466                   sums_l(k,13,tn) = sums_l(k,13,tn) + 0.5_wp *                                    &
     1467                                                     ( w(k,j,i-1) + w(k,j,i) )                     &
     1468                                                     * rho_air_zw(k)                               &
     1469                                                     * momentumflux_output_conversion(k)          &
     1470                                                     * ust * rmask(j,i,sr)                         &
    15731471                                                           * flag
    15741472!
    15751473!--                Momentum flux w*v*
    1576                    sums_l(k,15,tn) = sums_l(k,15,tn) + 0.5_wp *                &
    1577                                                      ( w(k,j-1,i) + w(k,j,i) ) &
    1578                                            * rho_air_zw(k)                     &
    1579                                            * momentumflux_output_conversion(k) &
    1580                                                      * vst * rmask(j,i,sr)     &
     1474                   sums_l(k,15,tn) = sums_l(k,15,tn) + 0.5_wp * ( w(k,j-1,i) + w(k,j,i) )          &
     1475                                                     * rho_air_zw(k)                               &
     1476                                                     * momentumflux_output_conversion(k)           &
     1477                                                     * vst * rmask(j,i,sr)                         &
    15811478                                                           * flag
    15821479                ENDDO
     
    15901487             DO  j = nys, nyn
    15911488                DO  k = nzb, nzt
    1592                    flag = MERGE( 1.0_wp, 0.0_wp,                               &
    1593                                  BTEST( wall_flags_total_0(k,j,i), 23 ) ) *    &
    1594                           MERGE( 1.0_wp, 0.0_wp,                               &
    1595                                  BTEST( wall_flags_total_0(k,j,i), 9  ) )
     1489                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 23 ) ) *        &
     1490                          MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 9  ) )
    15961491!
    15971492!--                Vertical heat flux
    1598                    sums_l(k,17,tn) = sums_l(k,17,tn) + 0.5_wp *                &
    1599                            ( pt(k,j,i)   - hom(k,1,4,sr) +                     &
    1600                              pt(k+1,j,i) - hom(k+1,1,4,sr) )                   &
    1601                            * rho_air_zw(k)                                     &
    1602                            * heatflux_output_conversion(k)                     &
    1603                            * w(k,j,i) * rmask(j,i,sr) * flag
     1493                   sums_l(k,17,tn) = sums_l(k,17,tn) + 0.5_wp *                                    &
     1494                                     ( pt(k,j,i)   - hom(k,1,4,sr) +                               &
     1495                                       pt(k+1,j,i) - hom(k+1,1,4,sr) )                             &
     1496                                     * rho_air_zw(k)                                               &
     1497                                     * heatflux_output_conversion(k)                               &
     1498                                     * w(k,j,i) * rmask(j,i,sr) * flag
    16041499                   IF ( humidity )  THEN
    1605                       pts = 0.5_wp * ( q(k,j,i)   - hom(k,1,41,sr) +           &
    1606                                       q(k+1,j,i) - hom(k+1,1,41,sr) )
    1607                       sums_l(k,49,tn) = sums_l(k,49,tn) + pts * w(k,j,i) *     &
    1608                                        rho_air_zw(k) *                         &
    1609                                        waterflux_output_conversion(k) *        &
    1610                                        rmask(j,i,sr) * flag
     1500                      pts = 0.5_wp * ( q(k,j,i)   - hom(k,1,41,sr) +                               &
     1501                                       q(k+1,j,i) - hom(k+1,1,41,sr) )
     1502                      sums_l(k,49,tn) = sums_l(k,49,tn) + pts * w(k,j,i) *                         &
     1503                                                          rho_air_zw(k) *                         &
     1504                                                          waterflux_output_conversion(k) *         &
     1505                                                          rmask(j,i,sr) * flag
    16111506                   ENDIF
    16121507                   IF ( passive_scalar )  THEN
    1613                       pts = 0.5_wp * ( s(k,j,i)   - hom(k,1,115,sr) +           &
    1614                                       s(k+1,j,i) - hom(k+1,1,115,sr) )
    1615                       sums_l(k,114,tn) = sums_l(k,114,tn) + pts * w(k,j,i) *    &
    1616                                         rmask(j,i,sr) * flag
     1508                      pts = 0.5_wp * ( s(k,j,i)   - hom(k,1,115,sr) +                              &
     1509                                       s(k+1,j,i) - hom(k+1,1,115,sr) )
     1510                      sums_l(k,114,tn) = sums_l(k,114,tn) + pts * w(k,j,i) *  rmask(j,i,sr) * flag
    16171511                   ENDIF
    16181512                ENDDO
     
    16301524
    16311525!
    1632 !--    Divergence of vertical flux of resolved scale energy and pressure
    1633 !--    fluctuations as well as flux of pressure fluctuation itself (68).
     1526!--    Divergence of vertical flux of resolved scale energy and pressure fluctuations as well as
     1527!--    flux of pressure fluctuation itself (68).
    16341528!--    First calculate the products, then the divergence.
    16351529!--    Calculation is time consuming. Do it only, if profiles shall be plotted.
    1636        IF ( hom(nzb+1,2,55,0) /= 0.0_wp  .OR.  hom(nzb+1,2,68,0) /= 0.0_wp )   &
    1637        THEN
     1530       IF ( hom(nzb+1,2,55,0) /= 0.0_wp  .OR.  hom(nzb+1,2,68,0) /= 0.0_wp )  THEN
    16381531          sums_ll = 0.0_wp  ! local array
    16391532
     
    16441537                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
    16451538
    1646                    sums_ll(k,1) = sums_ll(k,1) + 0.5_wp * w(k,j,i) * (         &
    1647                   ( 0.25_wp * ( u(k,j,i)+u(k+1,j,i)+u(k,j,i+1)+u(k+1,j,i+1) )  &
    1648                             - 0.5_wp * ( hom(k,1,1,sr) + hom(k+1,1,1,sr) ) )**2&
    1649                 + ( 0.25_wp * ( v(k,j,i)+v(k+1,j,i)+v(k,j+1,i)+v(k+1,j+1,i) )  &
    1650                             - 0.5_wp * ( hom(k,1,2,sr) + hom(k+1,1,2,sr) ) )**2&
    1651                 + w(k,j,i)**2                                        ) * flag * rmask(j,i,sr)
    1652 
    1653                    sums_ll(k,2) = sums_ll(k,2) + 0.5_wp * w(k,j,i)             &
    1654                                        * ( ( p(k,j,i) + p(k+1,j,i) )           &
    1655                                          / momentumflux_output_conversion(k) ) &
     1539                   sums_ll(k,1) = sums_ll(k,1) + 0.5_wp * w(k,j,i) * (                             &
     1540                                    ( 0.25_wp * ( u(k,j,i)+u(k+1,j,i)+u(k,j,i+1)+u(k+1,j,i+1) )    &
     1541                                              - 0.5_wp * ( hom(k,1,1,sr) + hom(k+1,1,1,sr) ) )**2  &
     1542                                  + ( 0.25_wp * ( v(k,j,i)+v(k+1,j,i)+v(k,j+1,i)+v(k+1,j+1,i) )    &
     1543                                              - 0.5_wp * ( hom(k,1,2,sr) + hom(k+1,1,2,sr) ) )**2  &
     1544                                  + w(k,j,i)**2                      ) * flag * rmask(j,i,sr)
     1545
     1546                   sums_ll(k,2) = sums_ll(k,2) + 0.5_wp * w(k,j,i)                                 &
     1547                                       * ( ( p(k,j,i) + p(k+1,j,i) )                               &
     1548                                         / momentumflux_output_conversion(k) )                     &
    16561549                                       * flag * rmask(j,i,sr)
    16571550
     
    16771570!
    16781571!--    Divergence of vertical flux of SGS TKE and the flux itself (69)
    1679        IF ( hom(nzb+1,2,57,0) /= 0.0_wp  .OR.  hom(nzb+1,2,69,0) /= 0.0_wp )   &
    1680        THEN
     1572       IF ( hom(nzb+1,2,57,0) /= 0.0_wp  .OR.  hom(nzb+1,2,69,0) /= 0.0_wp )  THEN
    16811573          !$OMP DO
    16821574          DO  i = nxl, nxr
     
    16861578                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
    16871579
    1688                    sums_l(k,57,tn) = sums_l(k,57,tn) - 0.5_wp * (              &
    1689                    (km(k,j,i)+km(k+1,j,i)) * (e(k+1,j,i)-e(k,j,i)) * ddzu(k+1) &
    1690                  - (km(k-1,j,i)+km(k,j,i)) * (e(k,j,i)-e(k-1,j,i)) * ddzu(k)   &
    1691                                                                 ) * ddzw(k)    &
     1580                   sums_l(k,57,tn) = sums_l(k,57,tn) - 0.5_wp * (                                  &
     1581                                       (km(k,j,i)+km(k+1,j,i)) * (e(k+1,j,i)-e(k,j,i)) * ddzu(k+1) &
     1582                                     - (km(k-1,j,i)+km(k,j,i)) * (e(k,j,i)-e(k-1,j,i)) * ddzu(k)   &
     1583                                                                ) * ddzw(k)                        &
    16921584                                                                  * flag * rmask(j,i,sr)
    16931585
    1694                    sums_l(k,69,tn) = sums_l(k,69,tn) - 0.5_wp * (              &
    1695                    (km(k,j,i)+km(k+1,j,i)) * (e(k+1,j,i)-e(k,j,i)) * ddzu(k+1) &
    1696                                                                 )  * flag * rmask(j,i,sr)
     1586                   sums_l(k,69,tn) = sums_l(k,69,tn) - 0.5_wp * (                                  &
     1587                                        ( km(k,j,i) + km(k+1,j,i) ) *                              &
     1588                                        ( e(k+1,j,i) - e(k,j,i) ) * ddzu(k+1)                      &
     1589                                                                ) * flag * rmask(j,i,sr)
    16971590
    16981591                ENDDO
     
    17161609!
    17171610!--                Subgrid horizontal heat fluxes u"pt", v"pt"
    1718                    sums_l(k,58,tn) = sums_l(k,58,tn) - 0.5_wp *                &
    1719                                                    ( kh(k,j,i) + kh(k,j,i-1) ) &
    1720                                                  * ( pt(k,j,i-1) - pt(k,j,i) ) &
    1721                                                * rho_air_zw(k)                 &
    1722                                                * heatflux_output_conversion(k) &
    1723                                                  * ddx * rmask(j,i,sr) * flag
    1724                    sums_l(k,61,tn) = sums_l(k,61,tn) - 0.5_wp *                &
    1725                                                    ( kh(k,j,i) + kh(k,j-1,i) ) &
    1726                                                  * ( pt(k,j-1,i) - pt(k,j,i) ) &
    1727                                                * rho_air_zw(k)                 &
    1728                                                * heatflux_output_conversion(k) &
    1729                                                  * ddy * rmask(j,i,sr) * flag
     1611                   sums_l(k,58,tn) = sums_l(k,58,tn) - 0.5_wp *                                    &
     1612                                                        ( kh(k,j,i) + kh(k,j,i-1) )                &
     1613                                                      * ( pt(k,j,i-1) - pt(k,j,i) )                &
     1614                                                      * rho_air_zw(k)                              &
     1615                                                      * heatflux_output_conversion(k)              &
     1616                                                      * ddx * rmask(j,i,sr) * flag
     1617                   sums_l(k,61,tn) = sums_l(k,61,tn) - 0.5_wp *                                    &
     1618                                                        ( kh(k,j,i) + kh(k,j-1,i) )                &
     1619                                                      * ( pt(k,j-1,i) - pt(k,j,i) )                &
     1620                                                      * rho_air_zw(k)                              &
     1621                                                      * heatflux_output_conversion(k)              &
     1622                                                      * ddy * rmask(j,i,sr) * flag
    17301623!
    17311624!--                Resolved horizontal heat fluxes u*pt*, v*pt*
    1732                    sums_l(k,59,tn) = sums_l(k,59,tn) +                         &
    1733                                                   ( u(k,j,i) - hom(k,1,1,sr) ) &
    1734                                     * 0.5_wp * ( pt(k,j,i-1) - hom(k,1,4,sr) + &
    1735                                                  pt(k,j,i)   - hom(k,1,4,sr) ) &
    1736                                                * heatflux_output_conversion(k) &
    1737                                                * flag
    1738                    pts = 0.5_wp * ( pt(k,j-1,i) - hom(k,1,4,sr) +              &
     1625                   sums_l(k,59,tn) = sums_l(k,59,tn) +              ( u(k,j,i) - hom(k,1,1,sr) )   &
     1626                                                      * 0.5_wp * ( pt(k,j,i-1) - hom(k,1,4,sr) +   &
     1627                                                                   pt(k,j,i)   - hom(k,1,4,sr) )   &
     1628                                                                 * heatflux_output_conversion(k)   &
     1629                                                                 * flag
     1630                   pts = 0.5_wp * ( pt(k,j-1,i) - hom(k,1,4,sr) +                                  &
    17391631                                    pt(k,j,i)   - hom(k,1,4,sr) )
    1740                    sums_l(k,62,tn) = sums_l(k,62,tn) +                         &
    1741                                                   ( v(k,j,i) - hom(k,1,2,sr) ) &
    1742                                     * 0.5_wp * ( pt(k,j-1,i) - hom(k,1,4,sr) + &
    1743                                                  pt(k,j,i)   - hom(k,1,4,sr) ) &
    1744                                                * heatflux_output_conversion(k) &
    1745                                                * flag
     1632                   sums_l(k,62,tn) = sums_l(k,62,tn) +              ( v(k,j,i) - hom(k,1,2,sr) )   &
     1633                                                      * 0.5_wp * ( pt(k,j-1,i) - hom(k,1,4,sr) +   &
     1634                                                                   pt(k,j,i)   - hom(k,1,4,sr) )   &
     1635                                                                 * heatflux_output_conversion(k)   &
     1636                                                                 * flag
    17461637                ENDDO
    17471638             ENDDO
     
    17731664          ENDIF
    17741665
    1775           fac = ( simulated_time - dt_3d - time_vert(nt) )                     &
    1776                 / ( time_vert(nt+1)-time_vert(nt) )
     1666          fac = ( simulated_time - dt_3d - time_vert(nt) ) / ( time_vert(nt+1)-time_vert(nt) )
    17771667
    17781668
    17791669          DO  k = nzb, nzt
    1780              sums_ls_l(k,0) = td_lsa_lpt(k,nt)                                 &
    1781                               + fac * ( td_lsa_lpt(k,nt+1) - td_lsa_lpt(k,nt) )
    1782              sums_ls_l(k,1) = td_lsa_q(k,nt)                                   &
    1783                               + fac * ( td_lsa_q(k,nt+1) - td_lsa_q(k,nt) )
     1670             sums_ls_l(k,0) = td_lsa_lpt(k,nt) + fac * ( td_lsa_lpt(k,nt+1) - td_lsa_lpt(k,nt) )
     1671             sums_ls_l(k,1) = td_lsa_q(k,nt)   + fac * ( td_lsa_q(k,nt+1)   - td_lsa_q(k,nt) )
    17841672          ENDDO
    17851673
     
    17871675          sums_ls_l(nzt+1,1) = sums_ls_l(nzt,1)
    17881676
    1789           IF ( large_scale_subsidence .AND. use_subsidence_tendencies )  THEN
     1677          IF ( large_scale_subsidence  .AND. use_subsidence_tendencies )  THEN
    17901678
    17911679             DO  k = nzb, nzt
    1792                 sums_ls_l(k,2) = td_sub_lpt(k,nt) + fac *                      &
    1793                                  ( td_sub_lpt(k,nt+1) - td_sub_lpt(k,nt) )
    1794                 sums_ls_l(k,3) = td_sub_q(k,nt) + fac *                        &
    1795                                  ( td_sub_q(k,nt+1) - td_sub_q(k,nt) )
     1680                sums_ls_l(k,2) = td_sub_lpt(k,nt) + fac * ( td_sub_lpt(k,nt+1) - td_sub_lpt(k,nt) )
     1681                sums_ls_l(k,3) = td_sub_q(k,nt)   + fac * ( td_sub_q(k,nt+1)   - td_sub_q(k,nt) )
    17961682             ENDDO
    17971683
     
    18061692       !$OMP PARALLEL PRIVATE( i, j, k, tn )
    18071693       !$ tn = omp_get_thread_num()
    1808        IF ( radiation .AND. radiation_scheme == 'rrtmg' )  THEN
     1694       IF ( radiation  .AND. radiation_scheme == 'rrtmg' )  THEN
    18091695          !$OMP DO
    18101696          DO  i = nxl, nxr
     
    18131699                   flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
    18141700
    1815                    sums_l(k,100,tn)  = sums_l(k,100,tn)  + rad_lw_in(k,j,i)    &
    1816                                        * rmask(j,i,sr) * flag
    1817                    sums_l(k,101,tn)  = sums_l(k,101,tn)  + rad_lw_out(k,j,i)   &
    1818                                        * rmask(j,i,sr) * flag
    1819                    sums_l(k,102,tn)  = sums_l(k,102,tn)  + rad_sw_in(k,j,i)    &
    1820                                        * rmask(j,i,sr) * flag
    1821                    sums_l(k,103,tn)  = sums_l(k,103,tn)  + rad_sw_out(k,j,i)   &
    1822                                        * rmask(j,i,sr) * flag
    1823                    sums_l(k,104,tn)  = sums_l(k,104,tn)  + rad_lw_cs_hr(k,j,i) &
    1824                                        * rmask(j,i,sr) * flag
    1825                    sums_l(k,105,tn)  = sums_l(k,105,tn)  + rad_lw_hr(k,j,i)    &
    1826                                        * rmask(j,i,sr) * flag
    1827                    sums_l(k,106,tn)  = sums_l(k,106,tn)  + rad_sw_cs_hr(k,j,i) &
    1828                                        * rmask(j,i,sr) * flag
    1829                    sums_l(k,107,tn)  = sums_l(k,107,tn)  + rad_sw_hr(k,j,i)    &
    1830                                        * rmask(j,i,sr) * flag
     1701                   sums_l(k,100,tn)  = sums_l(k,100,tn) + rad_lw_in(k,j,i)    * rmask(j,i,sr) * flag
     1702                   sums_l(k,101,tn)  = sums_l(k,101,tn) + rad_lw_out(k,j,i)   * rmask(j,i,sr) * flag
     1703                   sums_l(k,102,tn)  = sums_l(k,102,tn) + rad_sw_in(k,j,i)    * rmask(j,i,sr) * flag
     1704                   sums_l(k,103,tn)  = sums_l(k,103,tn) + rad_sw_out(k,j,i)   * rmask(j,i,sr) * flag
     1705                   sums_l(k,104,tn)  = sums_l(k,104,tn) + rad_lw_cs_hr(k,j,i) * rmask(j,i,sr) * flag
     1706                   sums_l(k,105,tn)  = sums_l(k,105,tn) + rad_lw_hr(k,j,i)    * rmask(j,i,sr) * flag
     1707                   sums_l(k,106,tn)  = sums_l(k,106,tn) + rad_sw_cs_hr(k,j,i) * rmask(j,i,sr) * flag
     1708                   sums_l(k,107,tn)  = sums_l(k,107,tn) + rad_sw_hr(k,j,i)    * rmask(j,i,sr) * flag
    18311709                ENDDO
    18321710             ENDDO
     
    18481726                                      sums_l(:,45:pr_palm,i)
    18491727             IF ( max_pr_user > 0 )  THEN
    1850                 sums_l(:,pr_palm+1:pr_palm+max_pr_user,0) = &
    1851                                    sums_l(:,pr_palm+1:pr_palm+max_pr_user,0) + &
    1852                                    sums_l(:,pr_palm+1:pr_palm+max_pr_user,i)
     1728                sums_l(:,pr_palm+1:pr_palm+max_pr_user,0) =                                        &
     1729                                                       sums_l(:,pr_palm+1:pr_palm+max_pr_user,0) + &
     1730                                                       sums_l(:,pr_palm+1:pr_palm+max_pr_user,i)
    18531731             ENDIF
    18541732
     
    18771755!--    Compute total sum from local sums
    18781756       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    1879        CALL MPI_ALLREDUCE( sums_l(nzb,1,0), sums(nzb,1), ngp_sums, MPI_REAL,   &
    1880                            MPI_SUM, comm2d, ierr )
     1757       CALL MPI_ALLREDUCE( sums_l(nzb,1,0), sums(nzb,1), ngp_sums, MPI_REAL, MPI_SUM, comm2d, ierr )
    18811758       IF ( large_scale_forcing )  THEN
    1882           CALL MPI_ALLREDUCE( sums_ls_l(nzb,2), sums(nzb,83), ngp_sums_ls,     &
    1883                               MPI_REAL, MPI_SUM, comm2d, ierr )
     1759          CALL MPI_ALLREDUCE( sums_ls_l(nzb,2), sums(nzb,83), ngp_sums_ls, MPI_REAL, MPI_SUM,      &
     1760                              comm2d, ierr )
    18841761       ENDIF
    18851762
     
    18871764          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    18881765          DO  i = 1, max_pr_cs
    1889              CALL MPI_ALLREDUCE( sums_l(nzb,pr_palm+max_pr_user+i,0),          &
    1890                                  sums(nzb,pr_palm+max_pr_user+i),              &
     1766             CALL MPI_ALLREDUCE( sums_l(nzb,pr_palm+max_pr_user+i,0),                              &
     1767                                 sums(nzb,pr_palm+max_pr_user+i),                                  &
    18911768                                 nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d, ierr )
    18921769          ENDDO
     
    19101787
    19111788!
    1912 !--    Final values are obtained by division by the total number of grid points
    1913 !--    used for summation. After that store profiles.
    1914 !--    Check, if statistical regions do contain at least one grid point at the
    1915 !--    respective k-level, otherwise division by zero will lead to undefined
    1916 !--    values, which may cause e.g. problems with NetCDF output
     1789!--    Final values are obtained by division by the total number of grid points used for summation.
     1790!--    After that store profiles.
     1791!--    Check, if statistical regions do contain at least one grid point at the respective k-level,
     1792!--    otherwise division by zero will lead to undefined values, which may cause e.g. problems with
     1793!--    NetCDF output.
    19171794!--    Profiles:
    19181795       DO  k = nzb, nzt+1
     
    19421819
    19431820!--    u* and so on
    1944 !--    As sums(nzb:nzb+3,pr_palm) are full 2D arrays (us, usws, vsws, ts) whose
    1945 !--    size is always ( nx + 1 ) * ( ny + 1 ), defined at the first grid layer
    1946 !--    above the topography, they are being divided by ngp_2dh(sr)
    1947        sums(nzb:nzb+3,pr_palm)    = sums(nzb:nzb+3,pr_palm)    / &
    1948                                     ngp_2dh(sr)
    1949        sums(nzb+12,pr_palm)       = sums(nzb+12,pr_palm)       / &    ! qs
    1950                                     ngp_2dh(sr)
    1951        sums(nzb+13,pr_palm)       = sums(nzb+13,pr_palm)       / &    ! ss
    1952                                     ngp_2dh(sr)
    1953        sums(nzb+14,pr_palm)       = sums(nzb+14,pr_palm)       / &    ! surface temperature
    1954                                     ngp_2dh(sr)
     1821!--    As sums(nzb:nzb+3,pr_palm) are full 2D arrays (us, usws, vsws, ts) whose size is always
     1822!--    ( nx + 1 ) * ( ny + 1 ), defined at the first grid layer above the topography, they are
     1823!--    divided by ngp_2dh(sr)
     1824       sums(nzb:nzb+3,pr_palm)    = sums(nzb:nzb+3,pr_palm)  /  ngp_2dh(sr)
     1825       sums(nzb+12,pr_palm)       = sums(nzb+12,pr_palm)     /  ngp_2dh(sr)    ! qs
     1826       sums(nzb+13,pr_palm)       = sums(nzb+13,pr_palm)     /  ngp_2dh(sr)    ! ss
     1827       sums(nzb+14,pr_palm)       = sums(nzb+14,pr_palm)     /  ngp_2dh(sr)    ! surface temperature
     1828
    19551829!--    eges, e*
    1956        sums(nzb+4:nzb+5,pr_palm)  = sums(nzb+4:nzb+5,pr_palm)  / &
    1957                                     ngp_3d(sr)
     1830       sums(nzb+4:nzb+5,pr_palm)  = sums(nzb+4:nzb+5,pr_palm)  /  ngp_3d(sr)
    19581831!--    Old and new divergence
    1959        sums(nzb+9:nzb+10,pr_palm) = sums(nzb+9:nzb+10,pr_palm) / &
    1960                                     ngp_3d_inner(sr)
     1832       sums(nzb+9:nzb+10,pr_palm) = sums(nzb+9:nzb+10,pr_palm) /  ngp_3d_inner(sr)
    19611833
    19621834!--    User-defined profiles
    19631835       IF ( max_pr_user > 0 )  THEN
    19641836          DO  k = nzb, nzt+1
    1965              sums(k,pr_palm+1:pr_palm+max_pr_user) = &
    1966                                     sums(k,pr_palm+1:pr_palm+max_pr_user) / &
    1967                                     ngp_2dh_s_inner(k,sr)
    1968           ENDDO
    1969        ENDIF
    1970 
    1971        IF ( air_chemistry ) THEN
     1837             sums(k,pr_palm+1:pr_palm+max_pr_user) =  sums(k,pr_palm+1:pr_palm+max_pr_user) /      &
     1838                                                      ngp_2dh_s_inner(k,sr)
     1839          ENDDO
     1840       ENDIF
     1841
     1842       IF ( air_chemistry )  THEN
    19721843          IF ( max_pr_cs > 0 )  THEN
    19731844             DO k = nzb, nzt+1
    1974                 sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) = &
    1975                                  sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) / &
    1976                                  ngp_2dh_s_inner(k,sr)
     1845                sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) =                                 &
     1846                                                sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) / &
     1847                                                ngp_2dh_s_inner(k,sr)
    19771848             ENDDO
    19781849          ENDIF
    19791850       ENDIF
    19801851
    1981        IF ( salsa ) THEN
     1852       IF ( salsa )  THEN
    19821853          IF ( max_pr_salsa > 0 )  THEN
    19831854             DO k = nzb, nzt+1
     
    20201891       hom(:,1,37,sr) = sums(:,37)     ! w*e*
    20211892       hom(:,1,38,sr) = sums(:,38)     ! w*3
    2022        hom(:,1,39,sr) = sums(:,38) / ( abs( sums(:,32) ) + 1E-20_wp )**1.5_wp   ! Sw
     1893       hom(:,1,39,sr) = sums(:,38) / ( ABS( sums(:,32) ) + 1E-20_wp )**1.5_wp   ! Sw
    20231894       hom(:,1,40,sr) = sums(:,40)     ! p
    20241895       hom(:,1,45,sr) = sums(:,45)     ! w"vpt"
     
    21241995       hom(:,1,120,sr) = rho_air_zw    ! rho_air_zw in Kg/m^3
    21251996
    2126        IF ( kolmogorov_length_scale ) THEN
     1997       IF ( kolmogorov_length_scale )  THEN
    21271998          hom(:,1,121,sr) = sums(:,121) * 1E3_wp  ! eta in mm
    21281999       ENDIF
     
    21522023!
    21532024!--    Determine the boundary layer height using two different schemes.
    2154 !--    First scheme: Starting from the Earth's (Ocean's) surface, look for the
    2155 !--    first relative minimum (maximum) of the total heat flux.
    2156 !--    The corresponding height is assumed as the boundary layer height, if it
    2157 !--    is less than 1.5 times the height where the heat flux becomes negative
    2158 !--    (positive) for the first time. Attention: the resolved vertical sensible
    2159 !--    heat flux (hom(:,1,17,sr) = w*pt*) is not known at the beginning because
    2160 !--    the calculation happens in advec_s_ws which is called after
    2161 !--    flow_statistics. Therefore z_i is directly taken from restart data at
    2162 !--    the beginning of restart runs.
    2163        IF ( TRIM( initializing_actions ) /= 'read_restart_data' .OR.           &
     2025!--    First scheme: Starting from the Earth's (Ocean's) surface, look for the first relative
     2026!--    minimum (maximum) of the total heat flux.
     2027!--    The corresponding height is assumed as the boundary layer height, if it is less than 1.5
     2028!--    times the height where the heat flux becomes negative (positive) for the first time.
     2029!--    Attention: the resolved vertical sensible heat flux (hom(:,1,17,sr) = w*pt*) is not known at
     2030!--    the beginning because the calculation happens in advec_s_ws which is called after
     2031!--    flow_statistics. Therefore z_i is directly taken from restart data at the beginning of
     2032!--    restart runs.
     2033       IF ( TRIM( initializing_actions ) /= 'read_restart_data'  .OR.                              &
    21642034            simulated_time_at_begin /= simulated_time ) THEN
    21652035
     
    21732043                   height = zw(k)
    21742044                ENDIF
    2175                 IF ( hom(k,1,18,sr) < -1.0E-8_wp  .AND.                        &
    2176                      hom(k-1,1,18,sr) > hom(k,1,18,sr) )  THEN
     2045                IF ( hom(k,1,18,sr) < -1.0E-8_wp  .AND.  hom(k-1,1,18,sr) > hom(k,1,18,sr) )  THEN
    21772046                   IF ( zw(k) < 1.5_wp * height )  THEN
    21782047                      z_i(1) = zw(k)
     
    21892058                   height = zw(k)
    21902059                ENDIF
    2191                 IF ( hom(k,1,18,sr) < -1.0E-8_wp  .AND.                        &
    2192                      hom(k+1,1,18,sr) > hom(k,1,18,sr) )  THEN
     2060                IF ( hom(k,1,18,sr) < -1.0E-8_wp  .AND.  hom(k+1,1,18,sr) > hom(k,1,18,sr) )  THEN
    21932061                   IF ( zw(k) < 1.5_wp * height )  THEN
    21942062                      z_i(1) = zw(k)
     
    22022070
    22032071!
    2204 !--       Second scheme: Gradient scheme from Sullivan et al. (1998), modified
    2205 !--       by Uhlenbrock(2006). The boundary layer height is the height with the
    2206 !--       maximal local temperature gradient: starting from the second (the
    2207 !--       last but one) vertical gridpoint, the local gradient must be at least
    2208 !--       0.2K/100m and greater than the next four gradients.
     2072!--       Second scheme: Gradient scheme from Sullivan et al. (1998), modified by Uhlenbrock(2006).
     2073!--       The boundary layer height is the height with the maximal local temperature gradient:
     2074!--       starting from the second (the last but one) vertical gridpoint, the local gradient must be
     2075!--       at least 0.2K/100m and greater than the next four gradients.
    22092076!--       WARNING: The threshold value of 0.2K/100m must be adjusted for the
    22102077!--       ocean case!
     
    22172084          IF ( ocean_mode )  THEN
    22182085             DO  k = nzt+1, nzb+5, -1
    2219                 IF ( dptdz(k) > dptdz_threshold  .AND.                         &
    2220                      dptdz(k) > dptdz(k-1)  .AND.  dptdz(k) > dptdz(k-2)  .AND.&
     2086                IF ( dptdz(k) > dptdz_threshold  .AND.                                             &
     2087                     dptdz(k) > dptdz(k-1)  .AND.  dptdz(k) > dptdz(k-2)  .AND.                    &
    22212088                     dptdz(k) > dptdz(k-3)  .AND.  dptdz(k) > dptdz(k-4) )  THEN
    22222089                   z_i(2) = zw(k-1)
     
    22262093          ELSE
    22272094             DO  k = nzb+1, nzt-3
    2228                 IF ( dptdz(k) > dptdz_threshold  .AND.                         &
    2229                      dptdz(k) > dptdz(k+1)  .AND.  dptdz(k) > dptdz(k+2)  .AND.&
     2095                IF ( dptdz(k) > dptdz_threshold  .AND.                                             &
     2096                     dptdz(k) > dptdz(k+1)  .AND.  dptdz(k) > dptdz(k+2)  .AND.                    &
    22302097                     dptdz(k) > dptdz(k+3)  .AND.  dptdz(k) > dptdz(k+4) )  THEN
    22312098                   z_i(2) = zw(k-1)
     
    22412108
    22422109!
    2243 !--    Determine vertical index which is nearest to the mean surface level
    2244 !--    height of the respective statistic region
     2110!--    Determine vertical index which is nearest to the mean surface level height of the respective
     2111!--    statistic region
    22452112       DO  k = nzb, nzt
    22462113          IF ( zw(k) >= mean_surface_level_height(sr) )  THEN
     
    22512118
    22522119!
    2253 !--    Computation of both the characteristic vertical velocity and
    2254 !--    the characteristic convective boundary layer temperature.
    2255 !--    The inversion height entering into the equation is defined with respect
    2256 !--    to the mean surface level height of the respective statistic region.
    2257 !--    The horizontal average at surface level index + 1 is input for the
    2258 !--    average temperature.
    2259        IF ( hom(k_surface_level,1,18,sr) > 1.0E-8_wp  .AND.  z_i(1) /= 0.0_wp )&
    2260        THEN
    2261           hom(nzb+8,1,pr_palm,sr) =                                            &
    2262              ( g / hom(k_surface_level+1,1,4,sr) *                             &
    2263              ( hom(k_surface_level,1,18,sr) /                                  &
    2264              ( heatflux_output_conversion(nzb) * rho_air(nzb) ) )              &
    2265              * ABS( z_i(1) - mean_surface_level_height(sr) ) )**0.333333333_wp
     2120!--    Computation of both the characteristic vertical velocity and the characteristic convective
     2121!--    boundary layer temperature.
     2122!--    The inversion height entering into the equation is defined with respect to the mean surface
     2123!--    level height of the respective statistic region.
     2124!--    The horizontal average at surface level index + 1 is input for the average temperature.
     2125       IF ( hom(k_surface_level,1,18,sr) > 1.0E-8_wp  .AND.  z_i(1) /= 0.0_wp )  THEN
     2126          hom(nzb+8,1,pr_palm,sr) =                                                                &
     2127                                   ( g / hom(k_surface_level+1,1,4,sr) *                           &
     2128                                   ( hom(k_surface_level,1,18,sr) /                                &
     2129                                   ( heatflux_output_conversion(nzb) * rho_air(nzb) ) )            &
     2130                                   * ABS( z_i(1) - mean_surface_level_height(sr) ) )**0.333333333_wp
    22662131       ELSE
    22672132          hom(nzb+8,1,pr_palm,sr)  = 0.0_wp
     
    22692134
    22702135!
    2271 !--    Collect the time series quantities. Please note, timeseries quantities
    2272 !--    which are collected from horizontally averaged profiles, e.g. wpt
    2273 !--    or pt(zp), are treated specially. In case of elevated model surfaces,
    2274 !--    index nzb+1 might be within topography and data will be zero. Therefore,
    2275 !--    take value for the first atmosphere index, which is topo_min_level+1.
     2136!--    Collect the time series quantities. Please note, timeseries quantities which are collected
     2137!--    from horizontally averaged profiles, e.g. wpt or pt(zp), are treated specially. In case of
     2138!--    elevated model surfaces, index nzb+1 might be within topography and data will be zero.
     2139!--    Therefore, take value for the first atmosphere index, which is topo_min_level+1.
    22762140       ts_value(1,sr) = hom(nzb+4,1,pr_palm,sr)        ! E
    22772141       ts_value(2,sr) = hom(nzb+5,1,pr_palm,sr)        ! E*
  • palm/trunk/SOURCE/global_min_max.f90

    r4429 r4646  
    1 !> @file global_min_max.f90
    2 !------------------------------------------------------------------------------!
     1!--------------------------------------------------------------------------------------------------!
    32! This file is part of the PALM model system.
    43!
    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/>.
     4! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     5! Public License as published by the Free Software Foundation, either version 3 of the License, or
     6! (at your option) any later version.
     7!
     8! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     9! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     10! Public License for more details.
     11!
     12! You should have received a copy of the GNU General Public License along with PALM. If not, see
     13! <http://www.gnu.org/licenses/>.
    1614!
    1715! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     16!--------------------------------------------------------------------------------------------------!
    1917!
    2018! Current revisions:
    2119! ------------------
    22 ! 
    23 ! 
     20!
     21!
    2422! Former revisions:
    2523! -----------------
    2624! $Id$
     25! file re-formatted to follow the PALM coding standard
     26!
     27! 4429 2020-02-27 15:24:30Z raasch
    2728! bugfix: cpp-directives added for serial mode
    28 ! 
     29!
    2930! 4360 2020-01-07 11:25:50Z suehring
    3031! OpenACC support added
    31 ! 
     32!
    3233! 4182 2019-08-22 15:20:23Z scharf
    3334! Corrected "Former revisions" section
    34 ! 
     35!
    3536! 3655 2019-01-07 16:51:22Z knoop
    3637! Corrected "Former revisions" section
     
    4344! ------------
    4445!> Determine the array minimum/maximum and the corresponding indices.
    45 !------------------------------------------------------------------------------!
    46  SUBROUTINE global_min_max( i1, i2, j1, j2, k1, k2, ar, mode, offset, value, &
    47                             value_ijk, value1, value1_ijk )
    48  
    49 
    50     USE indices,                                                               &
     46!--------------------------------------------------------------------------------------------------!
     47 SUBROUTINE global_min_max( i1, i2, j1, j2, k1, k2, ar, mode, offset, value, value_ijk, value1,    &
     48                            value1_ijk )
     49
     50
     51    USE indices,                                                                                   &
    5152        ONLY:  nbgp, ny, nx
    52        
     53
    5354    USE kinds
    54    
     55
    5556    USE pegrid
    5657
     
    7273    INTEGER(iwp) ::  k1             !<
    7374    INTEGER(iwp) ::  k2             !<
    74     INTEGER(iwp) ::  fmax_ijk(3)    !<
    75     INTEGER(iwp) ::  fmax_ijk_l(3)  !<
    76     INTEGER(iwp) ::  fmin_ijk(3)    !<
    77     INTEGER(iwp) ::  fmin_ijk_l(3)  !<
    7875    INTEGER(iwp) ::  value_ijk(3)   !<
    79    
    80     INTEGER(iwp), OPTIONAL ::  value1_ijk(3)  !<
    81    
    82     REAL(wp) ::  offset                 !<
    83     REAL(wp) ::  value                  !<
     76
     77    INTEGER(iwp), DIMENSION(3) ::  fmax_ijk    !<
     78    INTEGER(iwp), DIMENSION(3) ::  fmax_ijk_l  !<
     79    INTEGER(iwp), DIMENSION(3) ::  fmin_ijk    !<
     80    INTEGER(iwp), DIMENSION(3) ::  fmin_ijk_l  !<
     81
     82    INTEGER(iwp), DIMENSION(3), OPTIONAL ::  value1_ijk  !<
     83
     84    REAL(wp) ::  offset            !<
     85    REAL(wp) ::  value             !<
     86    REAL(wp), OPTIONAL ::  value1  !<
     87
    8488    REAL(wp) ::  ar(i1:i2,j1:j2,k1:k2)  !<
    85    
     89
    8690#if defined( __ibm )
    8791    REAL(sp) ::  fmax(2)    !<
     
    8993    REAL(sp) ::  fmin(2)    !<
    9094    REAL(sp) ::  fmin_l(2)  !<
    91              ! on 32bit-machines MPI_2REAL must not be replaced 
     95             ! on 32bit-machines MPI_2REAL must not be replaced
    9296             ! by MPI_2DOUBLE_PRECISION
    9397#else
    94     REAL(wp) ::  fmax(2)    !<
    95     REAL(wp) ::  fmax_l(2)  !<
    96     REAL(wp) ::  fmin(2)    !<
    97     REAL(wp) ::  fmin_l(2)  !<
    98 #endif
     98    REAL(wp), DIMENSION(2) ::  fmax    !<
     99    REAL(wp), DIMENSION(2) ::  fmax_l  !<
     100    REAL(wp), DIMENSION(2) ::  fmin    !<
     101    REAL(wp), DIMENSION(2) ::  fmin_l  !<
     102#endif
     103
    99104#if defined( _OPENACC )
     105    INTEGER(iwp) ::  count_eq   !< counter for locations of maximum
    100106    REAL(wp)     ::  red        !< scalar for reduction with OpenACC
    101     INTEGER(iwp) ::  count_eq   !< counter for locations of maximum
    102 #endif
    103     REAL(wp), OPTIONAL ::  value1  !<
     107#endif
    104108
    105109
     
    119123       fmin_l(2)  = myid
    120124       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    121        CALL MPI_ALLREDUCE( fmin_l, fmin, 1, MPI_2REAL, MPI_MINLOC, comm2d, &
    122                            ierr )
     125       CALL MPI_ALLREDUCE( fmin_l, fmin, 1, MPI_2REAL, MPI_MINLOC, comm2d, ierr )
    123126
    124127!
     
    127130       IF ( id_fmin /= 0 )  THEN
    128131          IF ( myid == 0 )  THEN
    129              CALL MPI_RECV( fmin_ijk, 3, MPI_INTEGER, id_fmin, 0, comm2d, &
    130                             status, ierr )
     132             CALL MPI_RECV( fmin_ijk, 3, MPI_INTEGER, id_fmin, 0, comm2d, status, ierr )
    131133          ELSEIF ( myid == id_fmin )  THEN
    132134             CALL MPI_SEND( fmin_ijk_l, 3, MPI_INTEGER, 0, 0, comm2d, ierr )
     
    160162       fmax_l(2)  = myid
    161163       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    162        CALL MPI_ALLREDUCE( fmax_l, fmax, 1, MPI_2REAL, MPI_MAXLOC, comm2d, &
    163                            ierr )
     164       CALL MPI_ALLREDUCE( fmax_l, fmax, 1, MPI_2REAL, MPI_MAXLOC, comm2d, ierr )
    164165
    165166!
     
    168169       IF ( id_fmax /= 0 )  THEN
    169170          IF ( myid == 0 )  THEN
    170              CALL MPI_RECV( fmax_ijk, 3, MPI_INTEGER, id_fmax, 0, comm2d, &
    171                             status, ierr )
     171             CALL MPI_RECV( fmax_ijk, 3, MPI_INTEGER, id_fmax, 0, comm2d, status, ierr )
    172172          ELSEIF ( myid == id_fmax )  THEN
    173173             CALL MPI_SEND( fmax_ijk_l, 3, MPI_INTEGER, 0, 0, comm2d, ierr )
     
    177177       ENDIF
    178178!
    179 !--    send the indices of the just determined array maximum to other PEs
     179!--    Send the indices of the just determined array maximum to other PEs
    180180       CALL MPI_BCAST( fmax_ijk, 3, MPI_INTEGER, 0, comm2d, ierr )
    181181#else
     
    226226       IF ( count_eq == 1 ) THEN
    227227!
    228 !--       We found a single maximum element and correctly got its position. Transfer its
    229 !--       value to handle the negative case correctly.
     228!--       We found a single maximum element and correctly got its position. Transfer its value to
     229!--       handle the negative case correctly.
    230230          !$ACC UPDATE HOST(ar(fmax_ijk_l(1):fmax_ijk_l(1),fmax_ijk_l(2),fmax_ijk_l(3)))
    231231       ELSE
     
    257257#if defined( _OPENACC )
    258258!
    259 !--       Close ELSE case from above
     259!--    Close ELSE case from above
    260260       ENDIF
    261261#endif
     
    263263!
    264264!--    Set a flag in case that the determined value is negative.
    265 !--    A constant offset has to be subtracted in order to handle the special
    266 !--    case i=0 correctly
     265!--    A constant offset has to be subtracted in order to handle the special case i=0 correctly.
    267266       IF ( ar(fmax_ijk_l(1),fmax_ijk_l(2),fmax_ijk_l(3)) < 0.0_wp )  THEN
    268267          fmax_ijk_l(1) = -fmax_ijk_l(1) - 10
     
    272271       fmax_l(2)  = myid
    273272       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    274        CALL MPI_ALLREDUCE( fmax_l, fmax, 1, MPI_2REAL, MPI_MAXLOC, comm2d, &
    275                            ierr )
     273       CALL MPI_ALLREDUCE( fmax_l, fmax, 1, MPI_2REAL, MPI_MAXLOC, comm2d, ierr )
    276274
    277275!
     
    280278       IF ( id_fmax /= 0 )  THEN
    281279          IF ( myid == 0 )  THEN
    282              CALL MPI_RECV( fmax_ijk, 3, MPI_INTEGER, id_fmax, 0, comm2d, &
    283                             status, ierr )
     280             CALL MPI_RECV( fmax_ijk, 3, MPI_INTEGER, id_fmax, 0, comm2d, status, ierr )
    284281          ELSEIF ( myid == id_fmax )  THEN
    285282             CALL MPI_SEND( fmax_ijk_l, 3, MPI_INTEGER, 0, 0, comm2d, ierr )
     
    311308          DO  j = j1, j2
    312309!
    313 !--          Attention: the lowest gridpoint is excluded here, because there
    314 !--          ---------  is no advection at nzb=0 and mode 'absoff' is only
    315 !--                     used for calculating u,v extrema for CFL-criteria
     310!--          Attention: the lowest gridpoint is excluded here, because there is no advection at
     311!--          ---------- nzb=0 and mode 'absoff' is only used for calculating u,v extrema for
     312!--                     CFL-criteria.
    316313             DO  i = i1+1, i2
    317314                IF ( ABS( ar(i,j,k) - offset ) > fmax_l(1) )  THEN
     
    327324!
    328325!--    Set a flag in case that the determined value is negative.
    329 !--    A constant offset has to be subtracted in order to handle the special
    330 !--    case i=0 correctly
     326!--    A constant offset has to be subtracted in order to handle the special case i=0 correctly.
    331327       IF ( ar(fmax_ijk_l(1),fmax_ijk_l(2),fmax_ijk_l(3)) < 0.0_wp )  THEN
    332328          fmax_ijk_l(1) = -fmax_ijk_l(1) - 10
     
    336332       fmax_l(2)  = myid
    337333       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    338        CALL MPI_ALLREDUCE( fmax_l, fmax, 1, MPI_2REAL, MPI_MAXLOC, comm2d, &
    339                            ierr )
     334       CALL MPI_ALLREDUCE( fmax_l, fmax, 1, MPI_2REAL, MPI_MAXLOC, comm2d, ierr )
    340335
    341336!
     
    344339       IF ( id_fmax /= 0 )  THEN
    345340          IF ( myid == 0 )  THEN
    346              CALL MPI_RECV( fmax_ijk, 3, MPI_INTEGER, id_fmax, 0, comm2d, &
    347                             status, ierr )
     341             CALL MPI_RECV( fmax_ijk, 3, MPI_INTEGER, id_fmax, 0, comm2d, status, ierr )
    348342          ELSEIF ( myid == id_fmax )  THEN
    349343             CALL MPI_SEND( fmax_ijk_l, 3, MPI_INTEGER, 0, 0, comm2d, ierr )
  • palm/trunk/SOURCE/gust_mod.f90

    r4535 r4646  
    11!> @file gust_mod.f90
    2 !------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
    4 !
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
    9 !
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
    13 !
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     2!--------------------------------------------------------------------------------------------------!
     3! This file is part of the PALM model system.
     4!
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4535 2020-05-15 12:07:23Z raasch
    2729! bugfix for restart data format query
    28 ! 
     30!
    2931! 4517 2020-05-03 14:29:30Z raasch
    3032! added restart with MPI-IO for reading local arrays
    31 ! 
     33!
    3234! 4495 2020-04-13 20:11:20Z raasch
    3335! restart data handling with MPI-IO added
    34 ! 
     36!
    3537! 4360 2020-01-07 11:25:50Z suehring
    36 ! CASE statement for dummy variable u2_av in gust_rrd_local changed to avoid
    37 ! unintended interdependencies with user-defined variables
    38 ! 
     38! CASE statement for dummy variable u2_av in gust_rrd_local changed to avoid unintended
     39! interdependencies with user-defined variables
     40!
    3941! 3837 2019-03-28 16:55:58Z knoop
    4042! unused variable for file index removed from rrd-subroutines parameter list
    41 ! 
     43!
    4244! 3725 2019-02-07 10:11:02Z raasch
    4345! dummy statement modified to avoid compiler warnings about unused variables
    44 ! 
     46!
    4547! 3685 2019-01-21 01:02:11Z knoop
    4648! Some interface calls moved to module_interface + cleanup
    47 ! 
     49!
    4850! 3665 2019-01-10 08:28:24Z raasch
    4951! dummy statements added to avoid compiler warnings about unused variables
    50 ! 
     52!
    5153! 3655 2019-01-07 16:51:22Z knoop
    5254! Bugfix: domain bounds of local_pf corrected
    53 ! 
    54 ! 
     55!
     56!
    5557! Interfaces concerning data output updated
    56 ! 
    57 ! 
     58!
     59!
    5860! renamed gust_par to gust_parameters
    59 ! 
    60 ! 
     61!
     62!
    6163! Initial interface definition
    6264!
    63 ! 
     65!
    6466! Description:
    6567! ------------
     
    6769!>
    6870!> @todo This is just a dummy module. The actual module ist not released yet.
    69 !------------------------------------------------------------------------------!
     71!--------------------------------------------------------------------------------------------------!
    7072 MODULE gust_mod
    7173
     
    7375        ONLY:  restart_data_format_output
    7476
    75     USE indices,                                                               &
     77    USE indices,                                                                                   &
    7678        ONLY:  nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt
    7779
     
    9496!
    9597!-- Public functions
    96     PUBLIC &
    97        gust_parin, &
    98        gust_check_parameters, &
    99        gust_check_data_output_pr, &
    100        gust_check_data_output, &
    101        gust_init_arrays, &
    102        gust_init, &
    103        gust_define_netcdf_grid, &
    104        gust_header, &
    105        gust_actions, &
    106        gust_prognostic_equations, &
    107        gust_swap_timelevel, &
    108        gust_3d_data_averaging, &
    109        gust_data_output_2d, &
    110        gust_data_output_3d, &
    111        gust_statistics, &
    112        gust_rrd_global, &
    113        gust_wrd_global, &
    114        gust_rrd_local, &
     98    PUBLIC                                                                                         &
     99       gust_parin,                                                                                 &
     100       gust_check_parameters,                                                                      &
     101       gust_check_data_output_pr,                                                                  &
     102       gust_check_data_output,                                                                     &
     103       gust_init_arrays,                                                                           &
     104       gust_init,                                                                                  &
     105       gust_define_netcdf_grid,                                                                    &
     106       gust_header,                                                                                &
     107       gust_actions,                                                                               &
     108       gust_prognostic_equations,                                                                  &
     109       gust_swap_timelevel,                                                                        &
     110       gust_3d_data_averaging,                                                                     &
     111       gust_data_output_2d,                                                                        &
     112       gust_data_output_3d,                                                                        &
     113       gust_statistics,                                                                            &
     114       gust_rrd_global,                                                                            &
     115       gust_wrd_global,                                                                            &
     116       gust_rrd_local,                                                                             &
    115117       gust_wrd_local
    116118!
    117119!-- Public parameters, constants and initial values
    118     PUBLIC &
     120    PUBLIC                                                                                         &
    119121       gust_module_enabled
    120122
     
    203205
    204206
    205 !------------------------------------------------------------------------------!
     207!--------------------------------------------------------------------------------------------------!
    206208! Description:
    207209! ------------
    208210!> Parin for &gust_parameters for gust module
    209 !------------------------------------------------------------------------------!
     211!--------------------------------------------------------------------------------------------------!
    210212    SUBROUTINE gust_parin
    211213
     
    215217       CHARACTER (LEN=80)  ::  line  !< dummy string that contains the current line of the parameter file
    216218
    217        NAMELIST /gust_parameters/  &
     219       NAMELIST /gust_parameters/                                                                  &
    218220          gust_module_enabled
    219221
     
    240242
    241243
    242 !------------------------------------------------------------------------------!
     244!--------------------------------------------------------------------------------------------------!
    243245! Description:
    244246! ------------
    245247!> Check parameters routine for gust module
    246 !------------------------------------------------------------------------------!
     248!--------------------------------------------------------------------------------------------------!
    247249    SUBROUTINE gust_check_parameters
    248250
     
    254256
    255257
    256 !------------------------------------------------------------------------------!
     258!--------------------------------------------------------------------------------------------------!
    257259! Description:
    258260! ------------
    259261!> Check data output of profiles for gust module
    260 !------------------------------------------------------------------------------!
     262!--------------------------------------------------------------------------------------------------!
    261263    SUBROUTINE gust_check_data_output_pr( variable, var_count, unit, dopr_unit )
    262264
     
    264266       IMPLICIT NONE
    265267
     268       CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    266269       CHARACTER (LEN=*) ::  unit      !<
    267270       CHARACTER (LEN=*) ::  variable  !<
    268        CHARACTER (LEN=*) ::  dopr_unit !< local value of dopr_unit
    269271
    270272       INTEGER(iwp) ::  var_count      !<
     
    276278    END SUBROUTINE gust_check_data_output_pr
    277279
    278 !------------------------------------------------------------------------------!
     280!--------------------------------------------------------------------------------------------------!
    279281! Description:
    280282! ------------
    281283!> Check data output for gust module
    282 !------------------------------------------------------------------------------!
     284!--------------------------------------------------------------------------------------------------!
    283285    SUBROUTINE gust_check_data_output( var, unit )
    284286
     
    296298
    297299
    298 !------------------------------------------------------------------------------!
     300!--------------------------------------------------------------------------------------------------!
    299301! Description:
    300302! ------------
    301303!> Allocate gust module arrays and define pointers
    302 !------------------------------------------------------------------------------!
     304!--------------------------------------------------------------------------------------------------!
    303305    SUBROUTINE gust_init_arrays
    304306
     
    310312
    311313
    312 !------------------------------------------------------------------------------!
     314!--------------------------------------------------------------------------------------------------!
    313315! Description:
    314316! ------------
    315317!> Initialization of the gust module
    316 !------------------------------------------------------------------------------!
     318!--------------------------------------------------------------------------------------------------!
    317319    SUBROUTINE gust_init
    318320
     
    324326
    325327
    326 !------------------------------------------------------------------------------!
     328!--------------------------------------------------------------------------------------------------!
    327329!
    328330! Description:
     
    330332!> Subroutine defining appropriate grid for netcdf variables.
    331333!> It is called out from subroutine netcdf.
    332 !------------------------------------------------------------------------------!
     334!--------------------------------------------------------------------------------------------------!
    333335    SUBROUTINE gust_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
    334336
     
    336338       IMPLICIT NONE
    337339
    338        CHARACTER (LEN=*), INTENT(IN)  ::  var         !<
    339        LOGICAL, INTENT(IN)           ::  found       !<
    340340       CHARACTER (LEN=*), INTENT(IN) ::  grid_x      !<
    341341       CHARACTER (LEN=*), INTENT(IN) ::  grid_y      !<
    342342       CHARACTER (LEN=*), INTENT(IN) ::  grid_z      !<
     343       CHARACTER (LEN=*), INTENT(IN) ::  var         !<
     344
     345       LOGICAL, INTENT(IN)           ::  found       !<
    343346
    344347!
     
    349352
    350353
    351 !------------------------------------------------------------------------------!
     354!--------------------------------------------------------------------------------------------------!
    352355! Description:
    353356! ------------
    354357!> Header output for gust module
    355 !------------------------------------------------------------------------------!
     358!--------------------------------------------------------------------------------------------------!
    356359    SUBROUTINE gust_header ( io )
    357360
     
    368371
    369372
    370 !------------------------------------------------------------------------------!
     373!--------------------------------------------------------------------------------------------------!
    371374! Description:
    372375! ------------
    373376!> Call for all grid points
    374 !------------------------------------------------------------------------------!
     377!--------------------------------------------------------------------------------------------------!
    375378    SUBROUTINE gust_actions( location )
    376379
     
    387390
    388391
    389 !------------------------------------------------------------------------------!
     392!--------------------------------------------------------------------------------------------------!
    390393! Description:
    391394! ------------
    392395!> Call for grid point i,j
    393 !------------------------------------------------------------------------------!
     396!--------------------------------------------------------------------------------------------------!
    394397    SUBROUTINE gust_actions_ij( i, j, location )
    395398
     
    409412
    410413
    411 !------------------------------------------------------------------------------!
     414!--------------------------------------------------------------------------------------------------!
    412415! Description:
    413416! ------------
    414417!> Call for all grid points
    415 !------------------------------------------------------------------------------!
     418!--------------------------------------------------------------------------------------------------!
    416419    SUBROUTINE gust_prognostic_equations()
    417420
     
    423426
    424427
    425 !------------------------------------------------------------------------------!
     428!--------------------------------------------------------------------------------------------------!
    426429! Description:
    427430! ------------
    428431!> Call for grid point i,j
    429 !------------------------------------------------------------------------------!
     432!--------------------------------------------------------------------------------------------------!
    430433    SUBROUTINE gust_prognostic_equations_ij( i, j, i_omp_start, tn )
    431434
    432435
    433436       INTEGER(iwp), INTENT(IN) ::  i            !< grid index in x-direction
     437       INTEGER(iwp), INTENT(IN) ::  i_omp_start  !< first loop index of i-loop in prognostic_equations
    434438       INTEGER(iwp), INTENT(IN) ::  j            !< grid index in y-direction
    435        INTEGER(iwp), INTENT(IN) ::  i_omp_start  !< first loop index of i-loop in prognostic_equations
    436439       INTEGER(iwp), INTENT(IN) ::  tn           !< task number of openmp task
    437440
     
    443446
    444447
    445 !------------------------------------------------------------------------------!
     448!--------------------------------------------------------------------------------------------------!
    446449! Description:
    447450! ------------
    448451!> Swapping of timelevels
    449 !------------------------------------------------------------------------------!
     452!--------------------------------------------------------------------------------------------------!
    450453    SUBROUTINE gust_swap_timelevel ( mod_count )
    451454
     
    462465
    463466
    464 !------------------------------------------------------------------------------!
     467!--------------------------------------------------------------------------------------------------!
    465468!
    466469! Description:
    467470! ------------
    468471!> Subroutine for averaging 3D data
    469 !------------------------------------------------------------------------------!
     472!--------------------------------------------------------------------------------------------------!
    470473    SUBROUTINE gust_3d_data_averaging( mode, variable )
    471474
     
    474477
    475478       CHARACTER (LEN=*) ::  mode    !<
    476        CHARACTER (LEN=*) :: variable !<
     479       CHARACTER (LEN=*) ::  variable !<
    477480
    478481!
     
    482485    END SUBROUTINE gust_3d_data_averaging
    483486
    484 !------------------------------------------------------------------------------!
     487!--------------------------------------------------------------------------------------------------!
    485488!
    486489! Description:
    487490! ------------
    488491!> Subroutine defining 2D output variables
    489 !------------------------------------------------------------------------------!
    490     SUBROUTINE gust_data_output_2d( av, variable, found, grid, mode, local_pf, &
    491                                     two_d, nzb_do, nzt_do, fill_value )
     492!--------------------------------------------------------------------------------------------------!
     493    SUBROUTINE gust_data_output_2d( av, variable, found, grid, mode, local_pf, two_d, nzb_do,      &
     494                                    nzt_do, fill_value )
    492495
    493496
     
    495498
    496499       CHARACTER (LEN=*), INTENT(INOUT) ::  grid       !< name of vertical grid
    497        CHARACTER (LEN=*), INTENT(IN) ::  mode       !< either 'xy', 'xz' or 'yz'
    498        CHARACTER (LEN=*), INTENT(IN) ::  variable   !< name of variable
     500       CHARACTER (LEN=*), INTENT(IN)    ::  mode       !< either 'xy', 'xz' or 'yz'
     501       CHARACTER (LEN=*), INTENT(IN)    ::  variable   !< name of variable
    499502
    500503       INTEGER(iwp), INTENT(IN) ::  av        !< flag for (non-)average output
     
    508511
    509512       REAL(wp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do), INTENT(INOUT) ::  local_pf !< local
    510           !< array to which output data is resorted to
     513                                                                                      !< array to which output data is resorted to
    511514
    512515!
     
    519522
    520523
    521 !------------------------------------------------------------------------------!
     524!--------------------------------------------------------------------------------------------------!
    522525!
    523526! Description:
    524527! ------------
    525528!> Subroutine defining 3D output variables
    526 !------------------------------------------------------------------------------!
     529!--------------------------------------------------------------------------------------------------!
    527530    SUBROUTINE gust_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    528531
     
    550553
    551554
    552 !------------------------------------------------------------------------------!
     555!--------------------------------------------------------------------------------------------------!
    553556! Description:
    554557! ------------
    555558!> This routine computes profile and timeseries data for the gust module.
    556 !------------------------------------------------------------------------------!
     559!--------------------------------------------------------------------------------------------------!
    557560    SUBROUTINE gust_statistics( mode, sr, tn, dots_max )
    558561
     
    573576
    574577
    575 !------------------------------------------------------------------------------!
     578!--------------------------------------------------------------------------------------------------!
    576579! Description:
    577580! ------------
    578581!> Read module-specific global restart data (Fortran binary format).
    579 !------------------------------------------------------------------------------!
     582!--------------------------------------------------------------------------------------------------!
    580583    SUBROUTINE gust_rrd_global_ftn( found )
    581584
    582585
    583        USE control_parameters,                                                 &
     586       USE control_parameters,                                                                     &
    584587           ONLY: length, restart_string
    585588
     
    608611
    609612
    610 !------------------------------------------------------------------------------!
     613!--------------------------------------------------------------------------------------------------!
    611614! Description:
    612615! ------------
    613616!> Read module-specific global restart data (MPI-IO).
    614 !------------------------------------------------------------------------------!
     617!--------------------------------------------------------------------------------------------------!
    615618    SUBROUTINE gust_rrd_global_mpi
    616619
     
    622625
    623626
    624 !------------------------------------------------------------------------------!
     627!--------------------------------------------------------------------------------------------------!
    625628! Description:
    626629! ------------
    627630!> Read module-specific local restart data arrays (Fortran binary format).
    628 !------------------------------------------------------------------------------!
    629     SUBROUTINE gust_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc,         &
    630                                    nxr_on_file, nynf, nync, nyn_on_file, nysf,     &
    631                                    nysc, nys_on_file, tmp_2d, tmp_3d, found )
     631!--------------------------------------------------------------------------------------------------!
     632    SUBROUTINE gust_rrd_local_ftn( k, nxlf, nxlc, nxl_on_file, nxrf, nxrc, nxr_on_file, nynf, nync,&
     633                                   nyn_on_file, nysf, nysc, nys_on_file, tmp_2d, tmp_3d, found )
    632634
    633635
     
    696698
    697699
    698 !------------------------------------------------------------------------------!
     700!--------------------------------------------------------------------------------------------------!
    699701! Description:
    700702! ------------
    701703!> Read module-specific local restart data arrays (MPI-IO).
    702 !------------------------------------------------------------------------------!
     704!--------------------------------------------------------------------------------------------------!
    703705    SUBROUTINE gust_rrd_local_mpi
    704706
     
    709711
    710712
    711 !------------------------------------------------------------------------------!
     713!--------------------------------------------------------------------------------------------------!
    712714! Description:
    713715! ------------
    714716!> This routine writes the respective restart data for the gust module.
    715 !------------------------------------------------------------------------------!
     717!--------------------------------------------------------------------------------------------------!
    716718    SUBROUTINE gust_wrd_global
    717719
     
    742744
    743745
    744 !------------------------------------------------------------------------------!
     746!--------------------------------------------------------------------------------------------------!
    745747! Description:
    746748! ------------
    747749!> This routine writes the respective restart data for the gust module.
    748 !------------------------------------------------------------------------------!
     750!--------------------------------------------------------------------------------------------------!
    749751    SUBROUTINE gust_wrd_local
    750752
  • palm/trunk/SOURCE/header.f90

    r4586 r4646  
    11! !> @file header.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/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4586 2020-07-01 16:16:43Z gronemeier
    2729! Renamed rif to Ri (gradient Richardson number, 1D model)
    2830! and zeta (= z_mo / ol, stability parameter, 3D model)
     
    6769!
    6870! 4069 2019-07-01 14:05:51Z Giersch
    69 ! Masked output running index mid has been introduced as a local variable to
    70 ! avoid runtime error (Loop variable has been modified) in time_integration
     71! Masked output running index mid has been introduced as a local variable to avoid runtime error
     72! (Loop variable has been modified) in time_integration
    7173!
    7274! 4023 2019-06-12 13:20:01Z maronga
     
    8688! ------------
    8789!> Writing a header with all important information about the current run.
    88 !> This subroutine is called three times, two times at the beginning
    89 !> (writing information on files RUN_CONTROL and HEADER) and one time at the
    90 !> end of the run, then writing additional information about CPU-usage on file
     90!> This subroutine is called three times, two times at the beginning (writing information on
     91!> files RUN_CONTROL and HEADER) and one time at the end of the run, then writing
     92!> additional information about CPU-usage on file
    9193!> header.
    92 !-----------------------------------------------------------------------------!
     94!--------------------------------------------------------------------------------------------------!
    9395 SUBROUTINE header
    9496
    9597
    96     USE arrays_3d,                                                             &
     98    USE arrays_3d,                                                                                 &
    9799        ONLY:  pt_init, q_init, s_init, sa_init, ug, vg, w_subs, zu, zw
    98100
    99     USE basic_constants_and_equations_mod,                                     &
     101    USE basic_constants_and_equations_mod,                                                         &
    100102        ONLY:  g, kappa
    101103
    102     USE bulk_cloud_model_mod,                                                  &
     104    USE bulk_cloud_model_mod,                                                                      &
    103105        ONLY:  bulk_cloud_model
    104106
    105107    USE control_parameters
    106108
    107     USE cpulog,                                                                &
     109    USE cpulog,                                                                                    &
    108110        ONLY:  log_point_s
    109111
    110     USE grid_variables,                                                        &
     112    USE grid_variables,                                                                            &
    111113        ONLY:  dx, dy
    112114
    113     USE indices,                                                               &
    114         ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
    115                nys_mg, nzt, nzt_mg, topo_top_ind
     115    USE indices,                                                                                   &
     116        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg, nys_mg, nzt, nzt_mg,     &
     117               topo_top_ind
    116118
    117119    USE kinds
    118120
    119     USE model_1d_mod,                                                          &
     121    USE model_1d_mod,                                                                              &
    120122        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
    121123
    122     USE module_interface,                                                      &
     124    USE module_interface,                                                                          &
    123125        ONLY:  module_interface_header
    124126
    125     USE netcdf_interface,                                                      &
     127    USE netcdf_interface,                                                                          &
    126128        ONLY:  netcdf_data_format, netcdf_data_format_string, netcdf_deflate
    127129
    128     USE ocean_mod,                                                             &
    129         ONLY:  ibc_sa_t, prho_reference, sa_surface,                           &
    130                sa_vertical_gradient, sa_vertical_gradient_level,               &
    131                sa_vertical_gradient_level_ind
    132 
    133     USE palm_date_time_mod,                                                    &
     130    USE ocean_mod,                                                                                 &
     131        ONLY:  ibc_sa_t, prho_reference, sa_surface, sa_vertical_gradient,                         &
     132               sa_vertical_gradient_level, sa_vertical_gradient_level_ind
     133
     134    USE palm_date_time_mod,                                                                        &
    134135        ONLY:  get_date_time
    135136
     
    137138
    138139#if defined( __parallel )
    139     USE pmc_handle_communicator,                                               &
     140    USE pmc_handle_communicator,                                                                   &
    140141        ONLY:  pmc_get_model_info
    141142
    142     USE pmc_interface,                                                         &
     143    USE pmc_interface,                                                                             &
    143144        ONLY:  nested_run, nesting_datatransfer_mode, nesting_mode
    144145#endif
    145146
    146     USE surface_mod,                                                           &
     147    USE surface_mod,                                                                               &
    147148        ONLY:  surf_def_h
    148149
    149     USE turbulence_closure_mod,                                                &
     150    USE turbulence_closure_mod,                                                                    &
    150151        ONLY:  rans_const_c, rans_const_sigma
    151152
     
    161162    CHARACTER (LEN=16) ::  begin_chr           !< string indication start time for the data output
    162163    CHARACTER (LEN=16) ::  coor_chr            !< dummy string
     164
     165    CHARACTER (LEN=23) ::  date_time_str       !< string for date and time information
    163166
    164167    CHARACTER (LEN=26) ::  ver_rev             !< string for run identification
     
    171174
    172175    CHARACTER (LEN=70) ::  char1               !< dummy varialbe used for various strings
    173     CHARACTER (LEN=70) ::  char2               !< string containing informating about the advected distance in case of Galilei transformation
    174     CHARACTER (LEN=23) ::  date_time_str       !< string for date and time information
     176    CHARACTER (LEN=70) ::  char2               !< string containing informating about the advected distance in case of Galilei
     177                                               !< transformation
    175178    CHARACTER (LEN=70) ::  dopr_chr            !< string indicating profile output variables
    176179    CHARACTER (LEN=70) ::  do2d_xy             !< string indicating 2D-xy output variables
     
    185188
    186189    CHARACTER (LEN=86) ::  coordinates         !< string indicating height coordinates for profile-prescribed variables
    187     CHARACTER (LEN=86) ::  gradients           !< string indicating gradients of profile-prescribed variables between the prescribed height coordinates
     190    CHARACTER (LEN=86) ::  gradients           !< string indicating gradients of profile-prescribed variables between the
     191                                               !< prescribed height coordinates
    188192    CHARACTER (LEN=86) ::  slices              !< string indicating grid coordinates of profile-prescribed subsidence velocity
    189193    CHARACTER (LEN=86) ::  temperatures        !< string indicating profile-prescribed subsidence velocities
     
    231235
    232236!
    233 !-- Open the output file. At the end of the simulation, output is directed
    234 !-- to unit 19.
    235     IF ( ( runnr == 0 .OR. force_print_header )  .AND. &
     237!-- Open the output file. At the end of the simulation, output is directed to unit 19.
     238    IF ( ( runnr == 0 .OR. force_print_header )  .AND.                                             &
    236239         .NOT. simulated_time_at_begin /= simulated_time )  THEN
    237240       io = 15   !  header output on file RUN_CONTROL
     
    242245
    243246!
    244 !-- At the end of the run, output file (HEADER) will be rewritten with
    245 !-- new information
     247!-- At the end of the run, output file (HEADER) will be rewritten with new information
    246248    IF ( io == 19 .AND. simulated_time_at_begin /= simulated_time ) REWIND( 19 )
    247249
     
    295297#endif
    296298    IF ( ensemble_member_nr /= 0 )  THEN
    297        WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr,           &
    298                        ADJUSTR( host_chr ), ensemble_member_nr
     299       WRITE ( io, 512 )  run_date, run_identifier, run_time, runnr, ADJUSTR( host_chr ),          &
     300                         ensemble_member_nr
    299301    ELSE
    300        WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr,           &
    301                        ADJUSTR( host_chr )
     302       WRITE ( io, 102 )  run_date, run_identifier, run_time, runnr, ADJUSTR( host_chr )
    302303    ENDIF
    303304#if defined( __parallel )
     
    310311       WRITE ( io, 103 )  numprocs, pdims(1), pdims(2), TRIM( char1 )
    311312    ELSE
    312        WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, &
    313                           threads_per_task, pdims(1), pdims(2), TRIM( char1 )
     313       WRITE ( io, 104 )  numprocs*threads_per_task, numprocs, threads_per_task, pdims(1),         &
     314                          pdims(2), TRIM( char1 )
    314315    ENDIF
    315316
     
    329330    IF ( nested_run )  THEN
    330331
    331        WRITE ( io, 600 )  TRIM( nesting_mode ),                                &
    332                           TRIM( nesting_datatransfer_mode )
     332       WRITE ( io, 600 )  TRIM( nesting_mode ), TRIM( nesting_datatransfer_mode )
    333333       CALL pmc_get_model_info( ncpl = ncpl, cpl_id = my_cpl_id )
    334334
    335335       DO  n = 1, ncpl
    336           CALL pmc_get_model_info( request_for_cpl_id = n, cpl_name = cpl_name,&
    337                                    cpl_parent_id = cpl_parent_id,              &
    338                                    lower_left_x = lower_left_coord_x,          &
    339                                    lower_left_y = lower_left_coord_y,          &
     336          CALL pmc_get_model_info( request_for_cpl_id = n, cpl_name = cpl_name,                    &
     337                                   cpl_parent_id = cpl_parent_id,                                  &
     338                                   lower_left_x = lower_left_coord_x,                              &
     339                                   lower_left_y = lower_left_coord_y,                              &
    340340                                   npe_total = npe_total )
    341341          IF ( n == my_cpl_id )  THEN
     
    344344             char1 = ' '
    345345          ENDIF
    346           WRITE ( io, 601 )  TRIM( char1 ), n, cpl_parent_id, npe_total,       &
    347                              lower_left_coord_x, lower_left_coord_y,           &
    348                              TRIM( cpl_name )
     346          WRITE ( io, 601 )  TRIM( char1 ), n, cpl_parent_id, npe_total, lower_left_coord_x,       &
     347                             lower_left_coord_y, TRIM( cpl_name )
    349348       ENDDO
    350349
     
    376375       ENDIF
    377376       IF ( mg_switch_to_pe0_level == 0 )  THEN
    378           WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
     377          WRITE ( io, 136 )  nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, nzt_mg(1)
     378       ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
     379          WRITE ( io, 137 )  mg_switch_to_pe0_level,                                               &
     380                             mg_loc_ind(2,0)-mg_loc_ind(1,0)+1,                                    &
     381                             mg_loc_ind(4,0)-mg_loc_ind(3,0)+1,                                    &
     382                             nzt_mg(mg_switch_to_pe0_level),                                       &
     383                             nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1,                         &
    379384                             nzt_mg(1)
    380        ELSEIF (  mg_switch_to_pe0_level /= -1 )  THEN
    381           WRITE ( io, 137 )  mg_switch_to_pe0_level,            &
    382                              mg_loc_ind(2,0)-mg_loc_ind(1,0)+1, &
    383                              mg_loc_ind(4,0)-mg_loc_ind(3,0)+1, &
    384                              nzt_mg(mg_switch_to_pe0_level),    &
    385                              nxr_mg(1)-nxl_mg(1)+1, nyn_mg(1)-nys_mg(1)+1, &
    386                              nzt_mg(1)
    387        ENDIF
    388        IF ( psolver == 'multigrid_noopt' .AND. masking_method )  WRITE ( io, 144 )
    389     ENDIF
    390     IF ( call_psolver_at_all_substeps  .AND. timestep_scheme(1:5) == 'runge' ) &
    391     THEN
     385       ENDIF
     386       IF ( psolver == 'multigrid_noopt'  .AND.  masking_method )  WRITE ( io, 144 )
     387    ENDIF
     388    IF ( call_psolver_at_all_substeps  .AND.  timestep_scheme(1:5) == 'runge' )  THEN
    392389       WRITE ( io, 142 )
    393390    ENDIF
     
    419416          char2 = 'at the end of the run'
    420417       ENDIF
    421        WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ),                        &
    422                           advected_distance_x/1000.0_wp,                       &
     418       WRITE ( io, 119 )  TRIM( char1 ), TRIM( char2 ), advected_distance_x/1000.0_wp,             &
    423419                          advected_distance_y/1000.0_wp
    424420    ENDIF
     
    427423    IF ( rayleigh_damping_factor /= 0.0_wp )  THEN
    428424       IF ( .NOT. ocean_mode )  THEN
    429           WRITE ( io, 123 )  'above', rayleigh_damping_height, &
    430                rayleigh_damping_factor
    431        ELSE
    432           WRITE ( io, 123 )  'below', rayleigh_damping_height, &
    433                rayleigh_damping_factor
     425          WRITE ( io, 123 )  'above', rayleigh_damping_height, rayleigh_damping_factor
     426       ELSE
     427          WRITE ( io, 123 )  'below', rayleigh_damping_height, rayleigh_damping_factor
    434428       ENDIF
    435429    ENDIF
     
    467461    WRITE ( io, 203 )  simulated_time_at_begin, end_time
    468462
    469     IF ( time_restart /= 9999999.9_wp  .AND. &
    470          simulated_time_at_begin == simulated_time )  THEN
     463    IF ( time_restart /= 9999999.9_wp  .AND.  simulated_time_at_begin == simulated_time )  THEN
    471464       IF ( dt_restart == 9999999.9_wp )  THEN
    472465          WRITE ( io, 204 )  ' Restart at:       ',time_restart
     
    481474          cpuseconds_per_simulated_second = 0.0_wp
    482475       ELSE
    483           cpuseconds_per_simulated_second = log_point_s(10)%sum / &
    484                                             ( simulated_time -    &
    485                                               simulated_time_at_begin )
    486        ENDIF
    487        WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,      &
    488                           log_point_s(10)%sum / REAL( i, KIND=wp ), &
    489                           cpuseconds_per_simulated_second
     476          cpuseconds_per_simulated_second = log_point_s(10)%sum /                                  &
     477                                            ( simulated_time - simulated_time_at_begin )
     478       ENDIF
     479       WRITE ( io, 206 )  simulated_time, log_point_s(10)%sum,                                     &
     480                          log_point_s(10)%sum / REAL( i, KIND=wp ), cpuseconds_per_simulated_second
    490481       IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < end_time )  THEN
    491482          IF ( dt_restart == 9999999.9_wp )  THEN
     
    499490
    500491!
    501 !-- Start time for coupled runs, if independent precursor runs for atmosphere
    502 !-- and ocean are used or have been used. In this case, coupling_start_time
    503 !-- defines the time when the coupling is switched on.
     492!-- Start time for coupled runs, if independent precursor runs for atmosphere and ocean are used or
     493!-- have been used. In this case, coupling_start_time defines the time when the coupling is
     494!-- switched on.
    504495    IF ( coupling_start_time /= 0.0_wp )  THEN
    505496       WRITE ( io, 207 )  coupling_start_time
     
    571562       ENDIF
    572563    ENDIF
    573     WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ),      &
    574                        MIN( nnz+2, nzt+2 )
     564    WRITE ( io, 254 )  nx, ny, nzt+1, MIN( nnx, nx+1 ), MIN( nny, ny+1 ), MIN( nnz+2, nzt+2 )
    575565    IF ( sloping_surface )  WRITE ( io, 260 )  alpha_surface
    576566
    577567!
    578 !-- Profile for the large scale vertial velocity
     568!-- Profile for the large scale vertial velocity.
    579569!-- Building output strings, starting with surface value
    580570    IF ( large_scale_subsidence )  THEN
     
    609599
    610600       IF ( .NOT. large_scale_forcing )  THEN
    611           WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), &
    612                              TRIM( gradients ), TRIM( slices )
    613        ENDIF
    614 
    615 
    616     ENDIF
    617 
    618 !-- Profile of the geostrophic wind (component ug)
     601          WRITE ( io, 426 )  TRIM( coordinates ), TRIM( temperatures ), TRIM( gradients ),         &
     602                             TRIM( slices )
     603       ENDIF
     604
     605
     606    ENDIF
     607
     608!-- Profile of the geostrophic wind (component ug).
    619609!-- Building output strings
    620610    WRITE ( ugcomponent, '(F6.2)' )  ug_surface
     
    646636
    647637    IF ( .NOT. large_scale_forcing )  THEN
    648        WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), &
    649                           TRIM( gradients ), TRIM( slices )
    650     ENDIF
    651 
    652 !-- Profile of the geostrophic wind (component vg)
     638       WRITE ( io, 423 )  TRIM( coordinates ), TRIM( ugcomponent ), TRIM( gradients ),             &
     639                          TRIM( slices )
     640    ENDIF
     641
     642!-- Profile of the geostrophic wind (component vg).
    653643!-- Building output strings
    654644    WRITE ( vgcomponent, '(F6.2)' )  vg_surface
     
    680670
    681671    IF ( .NOT. large_scale_forcing )  THEN
    682        WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), &
    683                           TRIM( gradients ), TRIM( slices )
     672       WRITE ( io, 424 )  TRIM( coordinates ), TRIM( vgcomponent ), TRIM( gradients ),             &
     673                          TRIM( slices )
    684674    ENDIF
    685675
     
    711701          byn = bys + bly
    712702
    713           WRITE ( io, 271 )  building_length_x, building_length_y, &
    714                              building_height, bxl, bxr, bys, byn
     703          WRITE ( io, 271 )  building_length_x, building_length_y, building_height, bxl, bxr, bys, &
     704                             byn
    715705
    716706       CASE ( 'single_street_canyon' )
     
    745735!
    746736!--          Tunnel axis in y direction
    747              IF ( tunnel_length == 9999999.9_wp  .OR.                          &
    748                   tunnel_length >= ( nx + 1 ) * dx )  THEN
    749                 WRITE ( io, 273 )  'y', tunnel_height, tunnel_wall_depth,      &
    750                                         tunnel_width_x
     737             IF ( tunnel_length == 9999999.9_wp  .OR.  tunnel_length >= ( nx + 1 ) * dx )  THEN
     738                WRITE ( io, 273 )  'y', tunnel_height, tunnel_wall_depth, tunnel_width_x
    751739             ELSE
    752                 WRITE ( io, 274 )  'y', tunnel_height, tunnel_wall_depth,      &
    753                                         tunnel_width_x, tunnel_length
     740                WRITE ( io, 274 )  'y', tunnel_height, tunnel_wall_depth, tunnel_width_x,          &
     741                                        tunnel_length
    754742             ENDIF
    755743
     
    757745!
    758746!--          Tunnel axis in x direction
    759              IF ( tunnel_length == 9999999.9_wp  .OR.                          &
    760                   tunnel_length >= ( ny + 1 ) * dy )  THEN
    761                 WRITE ( io, 273 )  'x', tunnel_height, tunnel_wall_depth,      &
    762                                         tunnel_width_y
     747             IF ( tunnel_length == 9999999.9_wp  .OR.  tunnel_length >= ( ny + 1 ) * dy )  THEN
     748                WRITE ( io, 273 )  'x', tunnel_height, tunnel_wall_depth, tunnel_width_y
    763749             ELSE
    764                 WRITE ( io, 274 )  'x', tunnel_height, tunnel_wall_depth,      &
    765                                         tunnel_width_y, tunnel_length
     750                WRITE ( io, 274 )  'x', tunnel_height, tunnel_wall_depth, tunnel_width_y,          &
     751                                        tunnel_length
    766752             ENDIF
    767753          ENDIF
     
    771757    IF ( TRIM( topography ) /= 'flat' )  THEN
    772758       IF ( TRIM( topography_grid_convention ) == ' ' )  THEN
    773           IF ( TRIM( topography ) == 'single_building' .OR.  &
     759          IF ( TRIM( topography ) == 'single_building' .OR.                                        &
    774760               TRIM( topography ) == 'single_street_canyon' )  THEN
    775761             WRITE ( io, 278 )
     
    931917          WRITE ( io, 316 )
    932918       ENDIF
    933        IF ( ocean_mode  .AND.  constant_top_salinityflux )                          &
    934           WRITE ( io, 309 )  top_salinityflux
     919       IF ( ocean_mode  .AND.  constant_top_salinityflux )  WRITE ( io, 309 )  top_salinityflux
    935920       IF ( humidity       )  WRITE ( io, 315 )
    936        IF ( passive_scalar .AND.  constant_top_scalarflux )                    &
    937           WRITE ( io, 302 ) top_scalarflux
     921       IF ( passive_scalar  .AND.  constant_top_scalarflux )  WRITE ( io, 302 ) top_scalarflux
    938922    ENDIF
    939923
    940924    IF ( constant_flux_layer )  THEN
    941        WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length,                     &
    942                           z0h_factor*roughness_length, kappa,                  &
     925       WRITE ( io, 305 )  (zu(1)-zu(0)), roughness_length, z0h_factor*roughness_length, kappa,     &
    943926                          zeta_min, zeta_max
    944927       IF ( .NOT. constant_heatflux )  WRITE ( io, 308 )
     
    950933       ENDIF
    951934    ELSE
    952        IF ( INDEX(initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
     935       IF ( INDEX( initializing_actions, 'set_1d-model_profiles') /= 0 )  THEN
    953936          WRITE ( io, 310 )  zeta_min, zeta_max
    954937       ENDIF
     
    959942       WRITE ( io, 318 )  use_cmax, pt_damping_width, pt_damping_factor
    960943       IF ( turbulent_inflow )  THEN
    961           IF ( y_shift == 0 ) THEN
    962              WRITE ( io, 319 )  recycling_width, recycling_plane, &
     944          IF ( y_shift == 0 )  THEN
     945             WRITE ( io, 319 )  recycling_width, recycling_plane,                                  &
    963946                                inflow_damping_height, inflow_damping_width
    964947          ELSE
    965              WRITE ( io, 322 )  y_shift, recycling_width, recycling_plane, &
     948             WRITE ( io, 322 )  y_shift, recycling_width, recycling_plane,                         &
    966949                                inflow_damping_height, inflow_damping_width
    967950          END IF
    968951       ENDIF
    969952       IF ( turbulent_outflow )  THEN
    970           WRITE ( io, 323 )  outflow_source_plane, INT(outflow_source_plane/dx)
     953          WRITE ( io, 323 )  outflow_source_plane, INT( outflow_source_plane / dx )
    971954       ENDIF
    972955    ENDIF
     
    989972    DO  WHILE ( pt_vertical_gradient_level_ind(i) /= -9999 )
    990973
    991        WRITE (coor_chr,'(F7.2)')  pt_init(pt_vertical_gradient_level_ind(i))
     974       WRITE ( coor_chr, '(F7.2)' )  pt_init(pt_vertical_gradient_level_ind(i))
    992975       temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
    993976
    994        WRITE (coor_chr,'(F7.2)')  pt_vertical_gradient(i)
     977       WRITE ( coor_chr, '(F7.2)' )  pt_vertical_gradient(i)
    995978       gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
    996979
    997        WRITE (coor_chr,'(I7)')  pt_vertical_gradient_level_ind(i)
     980       WRITE ( coor_chr, '(I7)' )  pt_vertical_gradient_level_ind(i)
    998981       slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
    999982
    1000        WRITE (coor_chr,'(F7.1)')  pt_vertical_gradient_level(i)
     983       WRITE ( coor_chr, '(F7.1)' )  pt_vertical_gradient_level(i)
    1001984       coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
    1002985
     
    1010993
    1011994    IF ( .NOT. nudging )  THEN
    1012        WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), &
    1013                           TRIM( gradients ), TRIM( slices )
     995       WRITE ( io, 420 )  TRIM( coordinates ), TRIM( temperatures ), TRIM( gradients ),            &
     996                          TRIM( slices )
    1014997    ELSE
    1015998       WRITE ( io, 428 )
     
    10271010       DO  WHILE ( q_vertical_gradient_level_ind(i) /= -9999 )
    10281011
    1029           WRITE (coor_chr,'(E8.1,4X)')  q_init(q_vertical_gradient_level_ind(i))
     1012          WRITE ( coor_chr, '(E8.1,4X)' )  q_init(q_vertical_gradient_level_ind(i))
    10301013          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
    10311014
    1032           WRITE (coor_chr,'(E8.1,4X)')  q_vertical_gradient(i)
     1015          WRITE ( coor_chr, '(E8.1,4X)' )  q_vertical_gradient(i)
    10331016          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
    10341017
    1035           WRITE (coor_chr,'(I8,4X)')  q_vertical_gradient_level_ind(i)
     1018          WRITE ( coor_chr, '(I8,4X)' )  q_vertical_gradient_level_ind(i)
    10361019          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
    10371020
    1038           WRITE (coor_chr,'(F8.1,4X)')  q_vertical_gradient_level(i)
     1021          WRITE ( coor_chr, '(F8.1,4X)' )  q_vertical_gradient_level(i)
    10391022          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
    10401023
     
    10481031
    10491032       IF ( .NOT. nudging )  THEN
    1050           WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ),        &
    1051                              TRIM( gradients ), TRIM( slices )
     1033          WRITE ( io, 421 )  TRIM( coordinates ), TRIM( temperatures ), TRIM( gradients ),         &
     1034                             TRIM( slices )
    10521035       ENDIF
    10531036    ENDIF
     
    10631046       DO  WHILE ( s_vertical_gradient_level_ind(i) /= -9999 )
    10641047
    1065           WRITE (coor_chr,'(E8.1,4X)')  s_init(s_vertical_gradient_level_ind(i))
     1048          WRITE ( coor_chr, '(E8.1,4X)' )  s_init(s_vertical_gradient_level_ind(i))
    10661049          temperatures = TRIM( temperatures ) // '  ' // TRIM( coor_chr )
    10671050
    1068           WRITE (coor_chr,'(E8.1,4X)')  s_vertical_gradient(i)
     1051          WRITE ( coor_chr, '(E8.1,4X)' )  s_vertical_gradient(i)
    10691052          gradients = TRIM( gradients ) // '  ' // TRIM( coor_chr )
    10701053
    1071           WRITE (coor_chr,'(I8,4X)')  s_vertical_gradient_level_ind(i)
     1054          WRITE ( coor_chr, '(I8,4X)' )  s_vertical_gradient_level_ind(i)
    10721055          slices = TRIM( slices ) // '  ' // TRIM( coor_chr )
    10731056
    1074           WRITE (coor_chr,'(F8.1,4X)')  s_vertical_gradient_level(i)
     1057          WRITE ( coor_chr, '(F8.1,4X)' )  s_vertical_gradient_level(i)
    10751058          coordinates = TRIM( coordinates ) // '  '  // TRIM( coor_chr )
    10761059
     
    10831066       ENDDO
    10841067
    1085        WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ),           &
    1086                           TRIM( gradients ), TRIM( slices )
     1068       WRITE ( io, 422 )  TRIM( coordinates ), TRIM( temperatures ), TRIM( gradients ),            &
     1069                          TRIM( slices )
    10871070    ENDIF
    10881071
     
    10981081       DO  WHILE ( sa_vertical_gradient_level_ind(i) /= -9999 )
    10991082
    1100           WRITE (coor_chr,'(F7.2)')  sa_init(sa_vertical_gradient_level_ind(i))
     1083          WRITE ( coor_chr, '(F7.2)' )  sa_init(sa_vertical_gradient_level_ind(i))
    11011084          temperatures = TRIM( temperatures ) // ' ' // TRIM( coor_chr )
    11021085
    1103           WRITE (coor_chr,'(F7.2)')  sa_vertical_gradient(i)
     1086          WRITE ( coor_chr, '(F7.2)' )  sa_vertical_gradient(i)
    11041087          gradients = TRIM( gradients ) // ' ' // TRIM( coor_chr )
    11051088
    1106           WRITE (coor_chr,'(I7)')  sa_vertical_gradient_level_ind(i)
     1089          WRITE ( coor_chr, '(I7)' )  sa_vertical_gradient_level_ind(i)
    11071090          slices = TRIM( slices ) // ' ' // TRIM( coor_chr )
    11081091
    1109           WRITE (coor_chr,'(F7.1)')  sa_vertical_gradient_level(i)
     1092          WRITE ( coor_chr, '(F7.1)' )  sa_vertical_gradient_level(i)
    11101093          coordinates = TRIM( coordinates ) // ' '  // TRIM( coor_chr )
    11111094
     
    11181101       ENDDO
    11191102
    1120        WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), &
    1121                           TRIM( gradients ), TRIM( slices )
     1103       WRITE ( io, 425 )  TRIM( coordinates ), TRIM( temperatures ), TRIM( gradients ),            &
     1104                          TRIM( slices )
    11221105    ENDIF
    11231106
     
    11951178       ENDDO
    11961179
    1197        IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.    &
    1198               ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.    &
     1180       IF ( ( ( do2d_xy /= ''  .AND.  section(1,1) /= -9999 )  .OR.                                &
     1181              ( do2d_xz /= ''  .AND.  section(1,2) /= -9999 )  .OR.                                &
    11991182              ( do2d_yz /= ''  .AND.  section(1,3) /= -9999 ) ) )  THEN
    12001183
     
    12241207             coordinates = '/'
    12251208!
    1226 !--          Building strings with index and coordinate information of the
    1227 !--          slices
     1209!--          Building strings with index and coordinate information of the slices
    12281210             DO  WHILE ( section(i,1) /= -9999 )
    12291211
     
    12331215
    12341216                IF ( section(i,1) == -1 )  THEN
    1235                    WRITE (coor_chr,'(F10.1)')  -1.0_wp
     1217                   WRITE ( coor_chr, '(F10.1)' )  -1.0_wp
    12361218                ELSE
    1237                    WRITE (coor_chr,'(F10.1)')  zu(section(i,1))
     1219                   WRITE ( coor_chr, '(F10.1)' )  zu(section(i,1))
    12381220                ENDIF
    12391221                coor_chr = ADJUSTL( coor_chr )
     
    12431225             ENDDO
    12441226             IF ( av == 0 )  THEN
    1245                 WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, &
    1246                                    TRIM( begin_chr ), 'k', TRIM( slices ), &
    1247                                    TRIM( coordinates )
     1227                WRITE ( io, 335 )  'XY', do2d_xy, dt_do2d_xy, TRIM( begin_chr ), 'k',              &
     1228                                   TRIM( slices ), TRIM( coordinates )
    12481229                IF ( skip_time_do2d_xy /= 0.0_wp )  THEN
    12491230                   WRITE ( io, 339 )  skip_time_do2d_xy
    12501231                ENDIF
    12511232             ELSE
    1252                 WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, &
    1253                                    TRIM( begin_chr ), averaging_interval, &
    1254                                    dt_averaging_input, 'k', TRIM( slices ), &
     1233                WRITE ( io, 342 )  'XY', do2d_xy, dt_data_output_av, TRIM( begin_chr ),            &
     1234                                   averaging_interval, dt_averaging_input, 'k', TRIM( slices ),    &
    12551235                                   TRIM( coordinates )
    12561236                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
     
    12701250             coordinates = '/'
    12711251!
    1272 !--          Building strings with index and coordinate information of the
    1273 !--          slices
     1252!--          Building strings with index and coordinate information of the slices
    12741253             DO  WHILE ( section(i,2) /= -9999 )
    12751254
     
    12851264             ENDDO
    12861265             IF ( av == 0 )  THEN
    1287                 WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, &
    1288                                    TRIM( begin_chr ), 'j', TRIM( slices ), &
    1289                                    TRIM( coordinates )
     1266                WRITE ( io, 335 )  'XZ', do2d_xz, dt_do2d_xz, TRIM( begin_chr ), 'j',              &
     1267                                   TRIM( slices ), TRIM( coordinates )
    12901268                IF ( skip_time_do2d_xz /= 0.0_wp )  THEN
    12911269                   WRITE ( io, 339 )  skip_time_do2d_xz
    12921270                ENDIF
    12931271             ELSE
    1294                 WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, &
    1295                                    TRIM( begin_chr ), averaging_interval, &
    1296                                    dt_averaging_input, 'j', TRIM( slices ), &
     1272                WRITE ( io, 342 )  'XZ', do2d_xz, dt_data_output_av, TRIM( begin_chr ),            &
     1273                                   averaging_interval, dt_averaging_input, 'j', TRIM( slices ),    &
    12971274                                   TRIM( coordinates )
    12981275                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
     
    13121289             coordinates = '/'
    13131290!
    1314 !--          Building strings with index and coordinate information of the
    1315 !--          slices
     1291!--          Building strings with index and coordinate information of the slices
    13161292             DO  WHILE ( section(i,3) /= -9999 )
    13171293
     
    13271303             ENDDO
    13281304             IF ( av == 0 )  THEN
    1329                 WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, &
    1330                                    TRIM( begin_chr ), 'i', TRIM( slices ), &
    1331                                    TRIM( coordinates )
     1305                WRITE ( io, 335 )  'YZ', do2d_yz, dt_do2d_yz, TRIM( begin_chr ), 'i',              &
     1306                                   TRIM( slices ), TRIM( coordinates )
    13321307                IF ( skip_time_do2d_yz /= 0.0_wp )  THEN
    13331308                   WRITE ( io, 339 )  skip_time_do2d_yz
    13341309                ENDIF
    13351310             ELSE
    1336                 WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, &
    1337                                    TRIM( begin_chr ), averaging_interval, &
    1338                                    dt_averaging_input, 'i', TRIM( slices ), &
     1311                WRITE ( io, 342 )  'YZ', do2d_yz, dt_data_output_av, TRIM( begin_chr ),            &
     1312                                   averaging_interval, dt_averaging_input, 'i', TRIM( slices ),    &
    13391313                                   TRIM( coordinates )
    13401314                IF ( skip_time_data_output_av /= 0.0_wp )  THEN
     
    13861360          ENDIF
    13871361          IF ( av == 0 )  THEN
    1388              WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), &
    1389                                 zu(nz_do3d), nz_do3d
     1362             WRITE ( io, 337 )  do3d_chr, dt_do3d, TRIM( begin_chr ), zu(nz_do3d), nz_do3d
    13901363          ELSE
    1391              WRITE ( io, 343 )  do3d_chr, dt_data_output_av,           &
    1392                                 TRIM( begin_chr ), averaging_interval, &
     1364             WRITE ( io, 343 )  do3d_chr, dt_data_output_av, TRIM( begin_chr ), averaging_interval,&
    13931365                                dt_averaging_input, zu(nz_do3d), nz_do3d
    13941366          ENDIF
     
    14151387
    14161388!
    1417 !-- masked arrays
    1418     IF ( masks > 0 )  WRITE ( io, 345 )  &
    1419          mask_scale_x, mask_scale_y, mask_scale_z
     1389!-- Masked arrays
     1390    IF ( masks > 0 )  WRITE ( io, 345 )  mask_scale_x, mask_scale_y, mask_scale_z
    14201391    DO  mid = 1, masks
    14211392       DO  av = 0, 1
     
    14241395          domask_chr = ''
    14251396          DO  WHILE ( domask(mid,av,i) /= ' ' )
    1426              domask_chr = TRIM( domask_chr ) // ' ' //  &
    1427                           TRIM( domask(mid,av,i) ) // ','
     1397             domask_chr = TRIM( domask_chr ) // ' ' // TRIM( domask(mid,av,i) ) // ','
    14281398             i = i + 1
    14291399          ENDDO
     
    14371407
    14381408             output_format = netcdf_data_format_string
    1439 !--          Parallel output not implemented for mask data, hence
    1440 !--          output_format must be adjusted.
     1409!
     1410!--          Parallel output not implemented for mask data, hence output_format must be adjusted.
    14411411             IF ( netcdf_data_format == 5 ) output_format = 'netCDF4/HDF5'
    14421412             IF ( netcdf_data_format == 6 ) output_format = 'netCDF4/HDF5 classic'
     
    14501420                WRITE ( io, 347 )  domask_chr, dt_domask(mid)
    14511421             ELSE
    1452                 WRITE ( io, 348 )  domask_chr, dt_data_output_av, &
    1453                                    averaging_interval, dt_averaging_input
     1422                WRITE ( io, 348 )  domask_chr, dt_data_output_av, averaging_interval,              &
     1423                                   dt_averaging_input
    14541424             ENDIF
    14551425
     
    14641434             ENDIF
    14651435!
    1466 !--          output locations
     1436!--          Output locations
    14671437             DO  dim = 1, 3
    14681438                IF ( mask(mid,dim,1) >= 0.0_wp )  THEN
     
    14711441                      count = count + 1
    14721442                   ENDDO
    1473                    WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), &
    1474                                       mask(mid,dim,:count)
    1475                 ELSEIF ( mask_loop(mid,dim,1) < 0.0_wp .AND.  &
    1476                          mask_loop(mid,dim,2) < 0.0_wp .AND.  &
     1443                   WRITE ( io, 349 )  dir(dim), dir(dim), mid, dir(dim), mask(mid,dim,:count)
     1444                ELSEIF ( mask_loop(mid,dim,1) <  0.0_wp .AND.                                      &
     1445                         mask_loop(mid,dim,2) <  0.0_wp .AND.                                      &
    14771446                         mask_loop(mid,dim,3) == 0.0_wp )  THEN
    14781447                   WRITE ( io, 350 )  dir(dim), dir(dim)
    14791448                ELSEIF ( mask_loop(mid,dim,3) == 0.0_wp )  THEN
    1480                    WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
    1481                                       mask_loop(mid,dim,1:2)
     1449                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), mask_loop(mid,dim,1:2)
    14821450                ELSE
    1483                    WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), &
    1484                                       mask_loop(mid,dim,1:3)
     1451                   WRITE ( io, 351 )  dir(dim), dir(dim), mid, dir(dim), mask_loop(mid,dim,1:3)
    14851452                ENDIF
    14861453             ENDDO
     
    15451512
    15461513!
    1547 !-- Cloud physcis parameters / quantities / numerical methods
     1514!-- Cloud physics parameters / quantities / numerical methods
    15481515    WRITE ( io, 430 )
    1549     IF ( humidity .AND. .NOT. bulk_cloud_model .AND. .NOT. cloud_droplets)  THEN
     1516    IF ( humidity  .AND.  .NOT. bulk_cloud_model  .AND. .NOT. cloud_droplets)  THEN
    15501517       WRITE ( io, 431 )
    15511518    ENDIF
     
    15581525!--
    15591526    IF ( constant_diffusion )  THEN
    1560        WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, &
    1561                           prandtl_number
     1527       WRITE ( io, 451 )  km_constant, km_constant/prandtl_number, prandtl_number
    15621528    ENDIF
    15631529    IF ( .NOT. constant_diffusion)  THEN
    15641530       IF ( e_init > 0.0_wp )  WRITE ( io, 455 )  e_init
    1565        IF ( e_min > 0.0_wp )  WRITE ( io, 454 )  e_min
     1531       IF ( e_min  > 0.0_wp )  WRITE ( io, 454 )  e_min
    15661532       IF ( wall_adjustment )  WRITE ( io, 453 )
    15671533    ENDIF
     
    15731539    WRITE ( io, 470 )
    15741540    IF ( create_disturbances )  THEN
    1575        WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                   &
    1576                           zu(disturbance_level_ind_b), disturbance_level_ind_b,&
     1541       WRITE ( io, 471 )  dt_disturb, disturbance_amplitude,                                       &
     1542                          zu(disturbance_level_ind_b), disturbance_level_ind_b,                    &
    15771543                          zu(disturbance_level_ind_t), disturbance_level_ind_t
    15781544       IF ( .NOT. bc_lr_cyc  .OR.  .NOT. bc_ns_cyc )  THEN
     
    15991565!-- Parameters of 1D-model
    16001566    IF ( INDEX( initializing_actions, 'set_1d-model_profiles' ) /= 0 )  THEN
    1601        WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, &
    1602                           mixing_length_1d, dissipation_1d
     1567       WRITE ( io, 500 )  end_time_1d, dt_run_control_1d, dt_pr_1d, mixing_length_1d, dissipation_1d
    16031568       IF ( damp_level_ind_1d /= nzt+1 )  THEN
    16041569          WRITE ( io, 502 )  zu(damp_level_ind_1d), damp_level_ind_1d
     
    16211586
    16221587 99 FORMAT (1X,78('-'))
    1623 100 FORMAT (/1X,'******************************',4X,44('-')/        &
    1624             1X,'* ',A,' *',4X,A/                               &
     1588100 FORMAT (/1X,'******************************',4X,44('-')/                                       &
     1589            1X,'* ',A,' *',4X,A/                                                                   &
    16251590            1X,'******************************',4X,44('-'))
    1626 101 FORMAT (35X,'coupled run: ',A/ &
     1591101 FORMAT (35X,'coupled run: ',A/                                                                 &
    16271592            35X,42('-'))
    1628 102 FORMAT (/' Date:               ',A10,4X,'Run:       ',A34/      &
    1629             ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/     &
     1593102 FORMAT (/' Date:               ',A10,4X,'Run:       ',A34/                                     &
     1594            ' Time:                 ',A8,4X,'Run-No.:   ',I2.2/                                    &
    16301595            ' Run on host:        ',A10)
    16311596#if defined( __parallel )
    1632 103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4, &
    1633               ')',1X,A)
    1634 104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/ &
     1597103 FORMAT (' Number of PEs:',10X,I6,4X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
     1598104 FORMAT (' Number of PEs:',10X,I6,4X,'Tasks:',I4,'   threads per task:',I4/                     &
    16351599              35X,'Processor grid (x,y): (',I4,',',I4,')',1X,A)
    16361600107 FORMAT (35X,'A 1d-decomposition along ',A,' is used')
    16371601108 FORMAT (35X,'Max. # of parallel I/O streams is ',I5)
    1638 109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/ &
     1602109 FORMAT (35X,'Precursor run for coupled atmos-ocean run'/                                       &
    16391603            35X,42('-'))
    1640 114 FORMAT (35X,'Coupled atmosphere-ocean run following'/ &
    1641             35X,'independent precursor runs'/             &
     1604114 FORMAT (35X,'Coupled atmosphere-ocean run following'/                                          &
     1605            35X,'independent precursor runs'/                                                      &
    16421606            35X,42('-'))
    16431607#endif
    1644 110 FORMAT (/' Numerical Schemes:'/ &
     1608110 FORMAT (/' Numerical Schemes:'/                                                                &
    16451609             ' -----------------'/)
    16461610124 FORMAT (' --> Use the ',A,' turbulence closure (',A,' mode).')
    16471611121 FORMAT (' --> Use the ',A,' approximation for the model equations.')
    16481612111 FORMAT (' --> Solve perturbation pressure via FFT using ',A,' routines')
    1649 112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/ &
     1613112 FORMAT (' --> Solve perturbation pressure via SOR-Red/Black-Schema'/                           &
    16501614            '     Iterations (initial/other): ',I3,'/',I3,'  omega =',F6.3)
    1651 113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)', &
    1652                   ' or Upstream')
     1615113 FORMAT (' --> Momentum advection via Piascek-Williams-Scheme (Form C3)',' or Upstream')
    16531616115 FORMAT ('     FFT and transpositions are overlapping')
    1654 116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)', &
    1655                   ' or Upstream')
     1617116 FORMAT (' --> Scalar advection via Piascek-Williams-Scheme (Form C3)',' or Upstream')
    16561618118 FORMAT (' --> Scalar advection via Bott-Chlond-Scheme')
    1657 119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/ &
    1658             '     translation velocity = ',A/ &
     1619119 FORMAT (' --> Galilei-Transform applied to horizontal advection:'/                             &
     1620            '     translation velocity = ',A/                                                      &
    16591621            '     distance advected ',A,':  ',F8.3,' km(x)  ',F8.3,' km(y)')
    16601622122 FORMAT (' --> Time differencing scheme: ',A)
    1661 123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/ &
     1623123 FORMAT (' --> Rayleigh-Damping active, starts ',A,' z = ',F8.2,' m'/                           &
    16621624            '     maximum damping coefficient:',F6.3, ' 1/s')
    16631625129 FORMAT (' --> Additional prognostic equation for the specific humidity')
    16641626130 FORMAT (' --> Additional prognostic equation for the total water content')
    1665 131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ', &
    1666                   F6.2, ' K assumed')
     1627131 FORMAT (' --> No pt-equation solved. Neutral stratification with pt = ',F6.2,' K assumed')
    16671628134 FORMAT (' --> Additional prognostic equation for a passive scalar')
    1668 135 FORMAT (' --> Solve perturbation pressure via ',A,' method (', &
    1669                   A,'-cycle)'/ &
    1670             '     number of grid levels:                   ',I2/ &
     1629135 FORMAT (' --> Solve perturbation pressure via ',A,' method (',A,'-cycle)'/                     &
     1630            '     number of grid levels:                   ',I2/                                   &
    16711631            '     Gauss-Seidel red/black iterations:       ',I2)
    1672 136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
    1673                   I3,')')
    1674 137 FORMAT ('     level data gathered on PE0 at level:     ',I2/ &
    1675             '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', &
    1676                   I3,')'/ &
    1677             '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', &
    1678                   I3,')')
     1632136 FORMAT ('     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', I3,')')
     1633137 FORMAT ('     level data gathered on PE0 at level:     ',I2/                                   &
     1634            '     gridpoints of coarsest subdomain (x,y,z): (',I3,',',I3,',', I3,')'/              &
     1635            '     gridpoints of coarsest domain (x,y,z):    (',I3,',',I3,',', I3,')')
    16791636139 FORMAT (' --> Loop optimization method: ',A)
    16801637140 FORMAT ('     maximum residual allowed:                ',E10.3)
    16811638141 FORMAT ('     fixed number of multigrid cycles:        ',I4)
    1682 142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ', &
    1683                   'step')
    1684 143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ', &
    1685                   'kinetic energy')
     1639142 FORMAT ('     perturbation pressure is calculated at every Runge-Kutta ','step')
     1640143 FORMAT ('     Euler/upstream scheme is used for the SGS turbulent ','kinetic energy')
    16861641144 FORMAT ('     masking method is used')
    1687 150 FORMAT (' --> Volume flow at the right and north boundary will be ', &
    1688                   'conserved'/ &
     1642150 FORMAT (' --> Volume flow at the right and north boundary will be ','conserved'/               &
    16891643            '     using the ',A,' mode')
    16901644151 FORMAT ('     with u_bulk = ',F7.3,' m/s and v_bulk = ',F7.3,' m/s')
    1691 152 FORMAT (' --> External pressure gradient directly prescribed by the user:',&
    1692            /'     ',2(1X,E12.5),'Pa/m in x/y direction', &
    1693            /'     starting from dp_level_b =', F8.3, 'm', A /)
    1694 200 FORMAT (//' Run time and time step information:'/ &
    1695              ' ----------------------------------'/)
    1696 201 FORMAT ( ' Timestep:             variable     maximum value: ',F6.3,' s', &
    1697              '    CFL-factor:',F5.2)
    1698 202 FORMAT ( ' Timestep:          dt = ',F6.3,' s'/)
    1699 203 FORMAT ( ' Start time:        ',F11.3,' s'/ &
     1645152 FORMAT (' --> External pressure gradient directly prescribed by the user:',                    &
     1646           /'     ',2(1X,E12.5),'Pa/m in x/y direction',                                           &
     1647           /'     starting from dp_level_b =',F8.3,'m',A/)
     1648200 FORMAT (//' Run time and time step information:'/                                              &
     1649            ' ----------------------------------'/)
     1650201 FORMAT (' Timestep:             variable     maximum value: ',F6.3,' s',                      &
     1651            '    CFL-factor:',F5.2)
     1652202 FORMAT (' Timestep:          dt = ',F6.3,' s'/)
     1653203 FORMAT (' Start time:        ',F11.3,' s'/                                                    &
    17001654             ' End time:          ',F11.3,' s')
    1701 204 FORMAT ( A,F11.3,' s')
    1702 205 FORMAT ( A,F11.3,' s',5X,'restart every',17X,F11.3,' s')
    1703 206 FORMAT (/' Time reached:      ',F11.3,' s'/ &
    1704              ' CPU-time used:       ',F9.3,' s     per timestep:                 ',F9.3,' s'/ &
     1655204 FORMAT (A,F11.3,' s')
     1656205 FORMAT (A,F11.3,' s',5X,'restart every',17X,F11.3,' s')
     1657206 FORMAT (/' Time reached:      ',F11.3,' s'/                                                    &
     1658             ' CPU-time used:       ',F9.3,' s     per timestep:                 ',F9.3,' s'/      &
    17051659             '                                      per second of simulated time: ',F9.3,' s')
    1706 207 FORMAT ( ' Spinup time:       ',F11.3,' s')
    1707 250 FORMAT (//' Computational grid and domain size:'/ &
    1708               ' ----------------------------------'// &
    1709               ' Grid length:      dx =    ',F8.3,' m    dy =    ',F8.3, ' m')
    1710 251 FORMAT (  /' Domain size:       x = ',F10.3,' m     y = ',F10.3, &
    1711               ' m  z(u) = ',F10.3,' m'/)
    1712 253 FORMAT ( '                dz(',I1,') =    ', F8.3, ' m')
    1713 254 FORMAT (//' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/ &
     1660207 FORMAT (' Spinup time:       ',F11.3,' s')
     1661250 FORMAT (//' Computational grid and domain size:'/                                              &
     1662              ' ----------------------------------'//                                              &
     1663              ' Grid length:      dx =    ',F8.3,' m    dy =    ',F8.3,' m')
     1664251 FORMAT (/' Domain size:       x = ',F10.3,' m     y = ',F10.3,' m  z(u) = ',F10.3,' m'/)
     1665253 FORMAT ('                dz(',I1,') =    ', F8.3, ' m')
     1666254 FORMAT (//' Number of gridpoints (x,y,z):  (0:',I4,', 0:',I4,', 0:',I4,')'/                    &
    17141667            ' Subdomain size (x,y,z):        (  ',I4,',   ',I4,',   ',I4,')'/)
    1715 260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,&
    1716              ' degrees')
    1717 270 FORMAT (//' Topography information:'/ &
    1718               ' ----------------------'// &
     1668260 FORMAT (/' The model has a slope in x-direction. Inclination angle: ',F6.2,' degrees')
     1669270 FORMAT (//' Topography information:'/                                                          &
     1670              ' ----------------------'//                                                          &
    17191671              1X,'Topography: ',A)
    1720 271 FORMAT (  ' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/ &
    1721               ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4, &
    1722                 ' / ',I4)
    1723 272 FORMAT (  ' Single quasi-2D street canyon of infinite length in ',A, &
    1724               ' direction' / &
    1725               ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      / &
    1726               ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
    1727 273 FORMAT (  ' Tunnel of infinite length in ',A, &
    1728               ' direction' / &
    1729               ' Tunnel height: ', F6.2, / &
    1730               ' Tunnel-wall depth: ', F6.2      / &
    1731               ' Tunnel width: ', F6.2 )
    1732 274 FORMAT (  ' Tunnel in ', A, ' direction.' / &
    1733               ' Tunnel height: ', F6.2, / &
    1734               ' Tunnel-wall depth: ', F6.2      / &
    1735               ' Tunnel width: ', F6.2, / &
    1736               ' Tunnel length: ', F6.2 )
    1737 278 FORMAT (' Topography grid definition convention:'/ &
    1738             ' cell edge (staggered grid points'/  &
     1672271 FORMAT (' Building size (x/y/z) in m: ',F5.1,' / ',F5.1,' / ',F5.1/                            &
     1673            ' Horizontal index bounds (l/r/s/n): ',I4,' / ',I4,' / ',I4,' / ',I4)
     1674272 FORMAT (' Single quasi-2D street canyon of infinite length in ',A,' direction' /               &
     1675            ' Canyon height: ', F6.2, 'm, ch = ', I4, '.'      /                                   &
     1676            ' Canyon position (',A,'-walls): cxl = ', I4,', cxr = ', I4, '.')
     1677273 FORMAT (' Tunnel of infinite length in ',A,                                                    &
     1678            ' direction' /                                                                         &
     1679            ' Tunnel height: ', F6.2, /                                                            &
     1680            ' Tunnel-wall depth: ', F6.2      /                                                    &
     1681            ' Tunnel width: ', F6.2 )
     1682274 FORMAT (' Tunnel in ', A, ' direction.' /                                                      &
     1683            ' Tunnel height: ', F6.2, /                                                            &
     1684            ' Tunnel-wall depth: ', F6.2      /                                                    &
     1685            ' Tunnel width: ', F6.2, /                                                             &
     1686            ' Tunnel length: ', F6.2 )
     1687278 FORMAT (' Topography grid definition convention:'/                                             &
     1688            ' cell edge (staggered grid points'/                                                   &
    17391689            ' (u in x-direction, v in y-direction))' /)
    1740 279 FORMAT (' Topography grid definition convention:'/ &
     1690279 FORMAT (' Topography grid definition convention:'/                                             &
    17411691            ' cell center (scalar grid points)' /)
    17421692280 FORMAT (' Complex terrain simulation is activated.')
    1743 281 FORMAT ('    --> Mean inflow profiles are adjusted.' / &
     1693281 FORMAT ('    --> Mean inflow profiles are adjusted.' /                                         &
    17441694            '    --> Elevation of inflow boundary: ', F7.1, ' m' )
    1745 282 FORMAT ('    --> Initial data from 3D-precursor run is shifted' / &
     1695282 FORMAT ('    --> Initial data from 3D-precursor run is shifted' /                              &
    17461696            '        vertically depending on local surface height.')
    1747 300 FORMAT (//' Boundary conditions:'/ &
    1748              ' -------------------'// &
    1749              '                     p                    uv             ', &
    1750              '                     pt'// &
    1751              ' B. bound.: ',A/ &
     1697300 FORMAT (//' Boundary conditions:'/                                                             &
     1698             ' -------------------'//                                                              &
     1699             '                     p                    uv             ',                          &
     1700             '                     pt'//                                                           &
     1701             ' B. bound.: ',A/                                                                     &
    17521702             ' T. bound.: ',A)
    1753 301 FORMAT (/'                     ',A// &
    1754              ' B. bound.: ',A/ &
     1703301 FORMAT (/'                     ',A//                                                           &
     1704             ' B. bound.: ',A/                                                                     &
    17551705             ' T. bound.: ',A)
    17561706303 FORMAT (/' Bottom surface fluxes are used in diffusion terms at k=1')
    17571707304 FORMAT (/' Top surface fluxes are used in diffusion terms at k=nzt')
    1758 305 FORMAT (//'    Constant flux layer between bottom surface and first ',     &
    1759               'computational u,v-level:'// &
    1760              '       z_mo = ',F6.2,' m   z0 =',F7.4,' m   z0h =',F8.5,&
    1761              ' m   kappa =',F5.2/ &
     1708305 FORMAT (//'    Constant flux layer between bottom surface and first ',                         &
     1709              'computational u,v-level:'//                                                         &
     1710             '       z_mo = ',F6.2,' m   z0 =',F7.4,' m   z0h =',F8.5,' m   kappa =',F5.2/         &
    17621711             '       zeta value range:   ',F8.2,' <= zeta <=',F6.2)
    17631712306 FORMAT ('       Predefined constant heatflux:   ',F9.6,' K m/s')
     
    17651714308 FORMAT ('       Predefined surface temperature')
    17661715309 FORMAT ('       Predefined constant salinityflux:   ',F9.6,' psu m/s')
    1767 310 FORMAT (//'    1D-Model:'// &
     1716310 FORMAT (//'    1D-Model:'//                                                                    &
    17681717             '       Ri value range:   ',F6.2,' <= Ri <=',F6.2)
    17691718311 FORMAT ('       Predefined constant humidity flux: ',E10.3,' kg/kg m/s')
     
    17731722302 FORMAT ('       Predefined constant scalarflux:   ',F9.6,' kg/(m**2 s)')
    17741723315 FORMAT ('       Humidity flux at top surface is 0.0')
    1775 316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', &
    1776                     'atmosphere model')
    1777 317 FORMAT (//' Lateral boundaries:'/ &
    1778             '       left/right:  ',A/    &
     1724316 FORMAT ('       Sensible heatflux and momentum flux from coupled ', 'atmosphere model')
     1725317 FORMAT (//' Lateral boundaries:'/                                                              &
     1726            '       left/right:  ',A/                                                              &
    17791727            '       north/south: ',A)
    1780 318 FORMAT (/'       use_cmax: ',L1 / &
    1781             '       pt damping layer width = ',F8.2,' m, pt ', &
    1782                     'damping factor =',F7.4)
    1783 319 FORMAT ('       turbulence recycling at inflow switched on'/ &
    1784             '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
     1728318 FORMAT (/'       use_cmax: ',L1 /                                                              &
     1729            '       pt damping layer width = ',F8.2,' m, pt ','damping factor =',F7.4)
     1730319 FORMAT ('       turbulence recycling at inflow switched on'/                                   &
     1731            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/                      &
    17851732            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m')
    1786 320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/ &
     1733320 FORMAT ('       Predefined constant momentumflux:  u: ',F9.6,' m**2/s**2'/                     &
    17871734            '                                          v: ',F9.6,' m**2/s**2')
    1788 321 FORMAT (//' Initial profiles:'/ &
     1735321 FORMAT (//' Initial profiles:'/                                                                &
    17891736              ' ----------------')
    1790 322 FORMAT ('       turbulence recycling at inflow switched on'/ &
    1791             '       y-shift of the recycled inflow turbulence is',I3,' PE'/ &
    1792             '       width of recycling domain: ',F7.1,' m   grid index: ',I4/ &
     1737322 FORMAT ('       turbulence recycling at inflow switched on'/                                   &
     1738            '       y-shift of the recycled inflow turbulence is',I3,' PE'/                        &
     1739            '       width of recycling domain: ',F7.1,' m   grid index: ',I4/                      &
    17931740            '       inflow damping height: ',F6.1,' m   width: ',F6.1,' m'/)
    1794 323 FORMAT ('       turbulent outflow conditon switched on'/ &
    1795             '       position of outflow source plane: ',F7.1,' m   ', &
    1796                     'grid index: ', I4)
    1797 325 FORMAT (//' List output:'/ &
    1798              ' -----------'//  &
    1799             '    1D-Profiles:'/    &
     1741323 FORMAT ('       turbulent outflow conditon switched on'/                                       &
     1742            '       position of outflow source plane: ',F7.1,' m   ','grid index: ', I4)
     1743325 FORMAT (//' List output:'/                                                                     &
     1744             ' -----------'//                                                                      &
     1745            '    1D-Profiles:'/                                                                    &
    18001746            '       Output every             ',F10.2,' s')
    1801 326 FORMAT ('       Time averaged over       ',F8.2,' s'/ &
     1747326 FORMAT ('       Time averaged over       ',F8.2,' s'/                                          &
    18021748            '       Averaging input every    ',F8.2,' s')
    1803 330 FORMAT (//' Data output:'/ &
     1749330 FORMAT (//' Data output:'/                                                                     &
    18041750             ' -----------'/)
    18051751331 FORMAT (/'    1D-Profiles:')
    18061752332 FORMAT (/'       ',A)
    1807 333 FORMAT ('       Output every             ',F8.2,' s',/ &
    1808             '       Time averaged over       ',F8.2,' s'/ &
     1753333 FORMAT ('       Output every             ',F8.2,' s',/                                         &
     1754            '       Time averaged over       ',F8.2,' s'/                                          &
    18091755            '       Averaging input every    ',F8.2,' s')
    18101756334 FORMAT (/'    2D-Arrays',A,':')
    1811 335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
    1812             '       Output every             ',F8.2,' s  ',A/ &
    1813             '       Cross sections at ',A1,' = ',A/ &
     1757335 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/                                            &
     1758            '       Output every             ',F8.2,' s  ',A/                                      &
     1759            '       Cross sections at ',A1,' = ',A/                                                &
    18141760            '       scalar-coordinates:   ',A,' m'/)
    18151761336 FORMAT (/'    3D-Arrays',A,':')
    18161762337 FORMAT (/'       Arrays: ',A/ &
    1817             '       Output every             ',F8.2,' s  ',A/ &
     1763            '       Output every             ',F8.2,' s  ',A/                                      &
    18181764            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
    18191765339 FORMAT ('       No output during initial ',F8.2,' s')
    18201766340 FORMAT (/'    Time series:')
    18211767341 FORMAT ('       Output every             ',F8.2,' s'/)
    1822 342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/ &
    1823             '       Output every             ',F8.2,' s  ',A/ &
    1824             '       Time averaged over       ',F8.2,' s'/ &
    1825             '       Averaging input every    ',F8.2,' s'/ &
    1826             '       Cross sections at ',A1,' = ',A/ &
     1768342 FORMAT (/'       ',A2,'-cross-section  Arrays: ',A/                                            &
     1769            '       Output every             ',F8.2,' s  ',A/                                      &
     1770            '       Time averaged over       ',F8.2,' s'/                                          &
     1771            '       Averaging input every    ',F8.2,' s'/                                          &
     1772            '       Cross sections at ',A1,' = ',A/                                                &
    18271773            '       scalar-coordinates:   ',A,' m'/)
    1828 343 FORMAT (/'       Arrays: ',A/ &
    1829             '       Output every             ',F8.2,' s  ',A/ &
    1830             '       Time averaged over       ',F8.2,' s'/ &
    1831             '       Averaging input every    ',F8.2,' s'/ &
     1774343 FORMAT (/'       Arrays: ',A/                                                                  &
     1775            '       Output every             ',F8.2,' s  ',A/                                      &
     1776            '       Time averaged over       ',F8.2,' s'/                                          &
     1777            '       Averaging input every    ',F8.2,' s'/                                          &
    18321778            '       Upper output limit at    ',F8.2,' m  (GP ',I4,')'/)
    18331779344 FORMAT ('       Output format: ',A/)
    1834 345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/ &
    1835             '       mask_scale_x (in x-direction): ',F9.3, ' m',/ &
    1836             '       mask_scale_y (in y-direction): ',F9.3, ' m',/ &
     1780345 FORMAT (/'    Scaling lengths for output locations of all subsequent mask IDs:',/              &
     1781            '       mask_scale_x (in x-direction): ',F9.3, ' m',/                                  &
     1782            '       mask_scale_y (in y-direction): ',F9.3, ' m',/                                  &
    18371783            '       mask_scale_z (in z-direction): ',F9.3, ' m' )
    18381784346 FORMAT (/'    Masked data output',A,' for mask ID ',I2, ':')
    1839 347 FORMAT ('       Variables: ',A/ &
     1785347 FORMAT ('       Variables: ',A/                                                                &
    18401786            '       Output every             ',F8.2,' s')
    18411787348 FORMAT ('       Variables: ',A/ &
    1842             '       Output every             ',F8.2,' s'/ &
    1843             '       Time averaged over       ',F8.2,' s'/ &
     1788            '       Output every             ',F8.2,' s'/                                          &
     1789            '       Time averaged over       ',F8.2,' s'/                                          &
    18441790            '       Averaging input every    ',F8.2,' s')
    1845 349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
    1846             'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/ &
     1791349 FORMAT (/'       Output locations in ',A,'-direction in multiples of ',                        &
     1792            'mask_scale_',A,' predefined by array mask_',I2.2,'_',A,':'/                           &
    18471793            13('       ',8(F8.2,',')/) )
    1848 350 FORMAT (/'       Output locations in ',A,'-direction: ', &
     1794350 FORMAT (/'       Output locations in ',A,'-direction: ',                                       &
    18491795            'all gridpoints along ',A,'-direction (default).' )
    1850 351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ', &
    1851             'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/ &
     1796351 FORMAT (/'       Output locations in ',A,'-direction in multiples of ',                        &
     1797            'mask_scale_',A,' constructed from array mask_',I2.2,'_',A,'_loop:'/                   &
    18521798            '          loop begin:',F8.2,', end:',F8.2,', stride:',F8.2 )
    1853 352 FORMAT  (/'       Number of output time levels allowed: ',I3 /)
    1854 353 FORMAT  (/'       Number of output time levels allowed: unlimited' /)
     1799352 FORMAT (/'       Number of output time levels allowed: ',I3 /)
     1800353 FORMAT (/'       Number of output time levels allowed: unlimited'/)
    18551801354 FORMAT ('       Output format: ',A, '   compressed with level: ',I1/)
    18561802355 FORMAT (/'    Restart data format(s):')
    18571803356 FORMAT ('    Input format:  ',A)
    18581804357 FORMAT ('    Output format: ',A)
    1859 400 FORMAT (//' Physical quantities:'/ &
     1805400 FORMAT (//' Physical quantities:'/                                                             &
    18601806              ' -------------------'/)
    1861 410 FORMAT ('    Geograph. latitude  :   latitude  = ',F5.1,' degr'/   &
    1862             '    Geograph. longitude :   longitude = ',F5.1,' degr'/   &
    1863             '    Rotation angle      :   rotation_angle = ',F5.1,' degr'/   &
    1864             '    Angular velocity    :   omega  =',E10.3,' rad/s'/  &
    1865             '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/    &
     1807410 FORMAT ('    Geograph. latitude  :   latitude  = ',F5.1,' degr'/                               &
     1808            '    Geograph. longitude :   longitude = ',F5.1,' degr'/                               &
     1809            '    Rotation angle      :   rotation_angle = ',F5.1,' degr'/                          &
     1810            '    Angular velocity    :   omega  =',E10.3,' rad/s'/                                 &
     1811            '    Coriolis parameter  :   f      = ',F9.6,' 1/s'/                                   &
    18661812            '                            f*     = ',F9.6,' 1/s')
    18671813411 FORMAT (/'    Gravity             :   g      = ',F4.1,' m/s**2')
     
    18691815413 FORMAT ('       Reference density in buoyancy terms: ',F8.3,' kg/m**3')
    18701816414 FORMAT ('       Reference temperature in buoyancy terms: ',F8.4,' K')
    1871 420 FORMAT (/'    Characteristic levels of the initial temperature profile:'// &
    1872             '       Height:        ',A,'  m'/ &
    1873             '       Temperature:   ',A,'  K'/ &
    1874             '       Gradient:      ',A,'  K/100m'/ &
     1817420 FORMAT (/'    Characteristic levels of the initial temperature profile:'//                     &
     1818            '       Height:        ',A,'  m'/                                                      &
     1819            '       Temperature:   ',A,'  K'/                                                      &
     1820            '       Gradient:      ',A,'  K/100m'/                                                 &
    18751821            '       Gridpoint:     ',A)
    1876 421 FORMAT (/'    Characteristic levels of the initial humidity profile:'// &
    1877             '       Height:      ',A,'  m'/ &
    1878             '       Humidity:    ',A,'  kg/kg'/ &
    1879             '       Gradient:    ',A,'  (kg/kg)/100m'/ &
     1822421 FORMAT (/'    Characteristic levels of the initial humidity profile:'//                        &
     1823            '       Height:      ',A,'  m'/                                                        &
     1824            '       Humidity:    ',A,'  kg/kg'/                                                    &
     1825            '       Gradient:    ',A,'  (kg/kg)/100m'/                                             &
    18801826            '       Gridpoint:   ',A)
    1881 422 FORMAT (/'    Characteristic levels of the initial scalar profile:'// &
    1882             '       Height:                  ',A,'  m'/ &
    1883             '       Scalar concentration:    ',A,'  kg/m**3'/ &
    1884             '       Gradient:                ',A,'  (kg/m**3)/100m'/ &
     1827422 FORMAT (/'    Characteristic levels of the initial scalar profile:'//                          &
     1828            '       Height:                  ',A,'  m'/                                            &
     1829            '       Scalar concentration:    ',A,'  kg/m**3'/                                      &
     1830            '       Gradient:                ',A,'  (kg/m**3)/100m'/                               &
    18851831            '       Gridpoint:               ',A)
    1886 423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'// &
    1887             '       Height:      ',A,'  m'/ &
    1888             '       ug:          ',A,'  m/s'/ &
    1889             '       Gradient:    ',A,'  1/100s'/ &
     1832423 FORMAT (/'    Characteristic levels of the geo. wind component ug:'//                          &
     1833            '       Height:      ',A,'  m'/                                                        &
     1834            '       ug:          ',A,'  m/s'/                                                      &
     1835            '       Gradient:    ',A,'  1/100s'/                                                   &
    18901836            '       Gridpoint:   ',A)
    1891 424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'// &
    1892             '       Height:      ',A,'  m'/ &
    1893             '       vg:          ',A,'  m/s'/ &
    1894             '       Gradient:    ',A,'  1/100s'/ &
     1837424 FORMAT (/'    Characteristic levels of the geo. wind component vg:'//                          &
     1838            '       Height:      ',A,'  m'/                                                        &
     1839            '       vg:          ',A,'  m/s'/                                                      &
     1840            '       Gradient:    ',A,'  1/100s'/                                                   &
    18951841            '       Gridpoint:   ',A)
    1896 425 FORMAT (/'    Characteristic levels of the initial salinity profile:'// &
    1897             '       Height:     ',A,'  m'/ &
    1898             '       Salinity:   ',A,'  psu'/ &
    1899             '       Gradient:   ',A,'  psu/100m'/ &
     1842425 FORMAT (/'    Characteristic levels of the initial salinity profile:'//                        &
     1843            '       Height:     ',A,'  m'/                                                         &
     1844            '       Salinity:   ',A,'  psu'/                                                       &
     1845            '       Gradient:   ',A,'  psu/100m'/                                                  &
    19001846            '       Gridpoint:  ',A)
    1901 426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'// &
    1902             '       Height:      ',A,'  m'/ &
    1903             '       w_subs:      ',A,'  m/s'/ &
    1904             '       Gradient:    ',A,'  (m/s)/100m'/ &
     1847426 FORMAT (/'    Characteristic levels of the subsidence/ascent profile:'//                       &
     1848            '       Height:      ',A,'  m'/                                                        &
     1849            '       w_subs:      ',A,'  m/s'/                                                      &
     1850            '       Gradient:    ',A,'  (m/s)/100m'/                                               &
    19051851            '       Gridpoint:   ',A)
    1906 427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'// &
     1852427 FORMAT (/'    Initial wind profiles (u,v) are interpolated from given'//                       &
    19071853                  ' profiles')
    1908 428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/ &
     1854428 FORMAT (/'    Initial profiles (u, v, pt, q) are taken from file '/                            &
    19091855             '    NUDGING_DATA')
    1910 430 FORMAT (//' Cloud physics quantities / methods:'/ &
     1856430 FORMAT (//' Cloud physics quantities / methods:'/                                              &
    19111857              ' ----------------------------------'/)
    19121858431 FORMAT ('    Humidity is considered, bu no condensation')
    1913 450 FORMAT (//' LES / Turbulence quantities:'/ &
     1859450 FORMAT (//' LES / Turbulence quantities:'/                                                     &
    19141860              ' ---------------------------'/)
    1915 451 FORMAT ('    Diffusion coefficients are constant:'/ &
     1861451 FORMAT ('    Diffusion coefficients are constant:'/                                            &
    19161862            '    Km = ',F6.2,' m**2/s   Kh = ',F6.2,' m**2/s   Pr = ',F5.2)
    19171863453 FORMAT ('    Mixing length is limited close to surfaces')
     
    19191865455 FORMAT ('    initial TKE is prescribed as ',E9.2,' (m/s)**2')
    19201866456 FORMAT (/'    Date and time at model start : ',A)
    1921 457 FORMAT ('    RANS-mode constants: c_0 = ',F9.5/         &
    1922             '                         c_1 = ',F9.5/         &
    1923             '                         c_2 = ',F9.5/         &
    1924             '                         c_3 = ',F9.5/         &
    1925             '                         c_4 = ',F9.5/         &
    1926             '                         sigma_e    = ',F9.5/  &
     1867457 FORMAT ('    RANS-mode constants: c_0 = ',F9.5/                                                &
     1868            '                         c_1 = ',F9.5/                                                &
     1869            '                         c_2 = ',F9.5/                                                &
     1870            '                         c_3 = ',F9.5/                                                &
     1871            '                         c_4 = ',F9.5/                                                &
     1872            '                         sigma_e    = ',F9.5/                                         &
    19271873            '                         sigma_diss = ',F9.5)
    1928 470 FORMAT (//' Actions during the simulation:'/ &
     1874470 FORMAT (//' Actions during the simulation:'/                                                   &
    19291875              ' -----------------------------'/)
    1930 471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/            &
    1931             '    Disturbance amplitude           :    ',F5.2, ' m/s'/       &
    1932             '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/  &
     1876471 FORMAT ('    Disturbance impulse (u,v) every :   ',F6.2,' s'/                                  &
     1877            '    Disturbance amplitude           :    ',F5.2, ' m/s'/                              &
     1878            '    Lower disturbance level         : ',F8.2,' m (GP ',I4,')'/                        &
    19331879            '    Upper disturbance level         : ',F8.2,' m (GP ',I4,')')
    1934 472 FORMAT ('    Disturbances continued during the run from i/j =',I4, &
    1935                  ' to i/j =',I4)
    1936 473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',&
    1937                  F6.3, ' m**2/s**2')
     1880472 FORMAT ('    Disturbances continued during the run from i/j =',I4,' to i/j =',I4)
     1881473 FORMAT ('    Disturbances cease as soon as the disturbance energy exceeds',F6.3, ' m**2/s**2')
    19381882474 FORMAT ('    Random number generator used    : ',A/)
    1939 475 FORMAT ('    The surface temperature is increased (or decreased, ', &
    1940                  'respectively, if'/ &
    1941             '    the value is negative) by ',F5.2,' K at the beginning of the',&
    1942                  ' 3D-simulation'/)
    1943 476 FORMAT ('    The surface temperature increases (or decreases, ', &
    1944                  'respectively, if'/ &
    1945             '    the value is negative) by ',F8.4,' K/h during the', &
    1946                  ' 3D-simulation'/)
    1947 477 FORMAT ('    The surface humidity is increased (or decreased, ',&
    1948                  'respectively, if the'/ &
    1949             '    value is negative) by ',E8.1,' kg/kg at the beginning of', &
    1950                  ' the 3D-simulation'/)
    1951 478 FORMAT ('    The scalar value is increased at the surface (or decreased, ',&
    1952                  'respectively, if the'/ &
    1953             '    value is negative) by ',E8.1,' kg/m**3 at the beginning of', &
    1954                  ' the 3D-simulation'/)
    1955 500 FORMAT (//' 1D-Model parameters:'/                           &
    1956               ' -------------------'//                           &
    1957             '    Simulation time:                   ',F8.1,' s'/ &
    1958             '    Run-controll output every:         ',F8.1,' s'/ &
    1959             '    Vertical profile output every:     ',F8.1,' s'/ &
    1960             '    Mixing length calculation:         ',A/         &
     1883475 FORMAT ('    The surface temperature is increased (or decreased, ','respectively, if'/         &
     1884            '    the value is negative) by ',F5.2,' K at the beginning of the',' 3D-simulation'/)
     1885476 FORMAT ('    The surface temperature increases (or decreases, ','respectively, if'/            &
     1886            '    the value is negative) by ',F8.4,' K/h during the',' 3D-simulation'/)
     1887477 FORMAT ('    The surface humidity is increased (or decreased, ','respectively, if the'/        &
     1888            '    value is negative) by ',E8.1,' kg/kg at the beginning of',' the 3D-simulation'/)
     1889478 FORMAT ('    The scalar value is increased at the surface (or decreased, ',                    &
     1890                 'respectively, if the'/                                                           &
     1891            '    value is negative) by ',E8.1,' kg/m**3 at the beginning of',' the 3D-simulation'/)
     1892500 FORMAT (//' 1D-Model parameters:'/                                                             &
     1893              ' -------------------'//                                                             &
     1894            '    Simulation time:                   ',F8.1,' s'/                                   &
     1895            '    Run-controll output every:         ',F8.1,' s'/                                   &
     1896            '    Vertical profile output every:     ',F8.1,' s'/                                   &
     1897            '    Mixing length calculation:         ',A/                                           &
    19611898            '    Dissipation calculation:           ',A/)
    19621899502 FORMAT ('    Damping layer starts from ',F7.1,' m (GP ',I4,')'/)
    19631900503 FORMAT (' --> Momentum advection via Wicker-Skamarock-Scheme 5th order')
    19641901504 FORMAT (' --> Scalar advection via Wicker-Skamarock-Scheme 5th order')
    1965 512 FORMAT (/' Date:               ',A10,6X,'Run:       ',A34/      &
    1966             ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/     &
     1902512 FORMAT (/' Date:               ',A10,6X,'Run:       ',A34/                                     &
     1903            ' Time:                 ',A8,6X,'Run-No.:   ',I2.2/                                    &
    19671904            ' Run on host:        ',A10,6X,'En-No.:    ',I2.2)
    19681905#if defined( __parallel )
    1969 600 FORMAT (/' Nesting informations:'/ &
    1970             ' --------------------'/ &
    1971             ' Nesting mode:                     ',A/ &
    1972             ' Nesting-datatransfer mode:        ',A// &
    1973             ' Nest id  parent  number   lower left coordinates   name'/ &
    1974             ' (*=me)     id    of PEs      x (m)     y (m)' )
     1906600 FORMAT (/' Nesting informations:'/                                                             &
     1907            ' --------------------'/                                                               &
     1908            ' Nesting mode:                     ',A/                                               &
     1909            ' Nesting-datatransfer mode:        ',A//                                              &
     1910            ' Nest id  parent  number   lower left coordinates   name'/                            &
     1911            ' (*=me)     id    of PEs      x (m)     y (m)')
    19751912601 FORMAT (2X,A1,1X,I2.2,6X,I2.2,5X,I5,5X,F8.2,2X,F8.2,5X,A)
    19761913#endif
  • palm/trunk/SOURCE/indoor_model_mod.f90

    r4481 r4646  
    11!> @file indoor_model_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/>.
     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/>.
    1615!
    1716! Copyright 2018-2020 Leibniz Universitaet Hannover
    1817! Copyright 2018-2020 Hochschule Offenburg
    19 !--------------------------------------------------------------------------------!
     18!--------------------------------------------------------------------------------------------------!
    2019!
    2120! Current revisions:
    2221! -----------------
    23 ! 
    24 ! 
     22!
     23!
    2524! Former revisions:
    2625! -----------------
    2726! $Id$
    28 ! Change order of dimension in surface array %frac to allow for better
    29 ! vectorization.
    30 !
     27! file re-formatted to follow the PALM coding standard
     28!
     29! 4481 2020-03-31 18:55:54Z maronga
     30! Change order of dimension in surface array %frac to allow for better vectorization.
     31!
    3132! 4441 2020-03-04 19:20:35Z suehring
    32 ! Major bugfix in calculation of energy demand - floor-area-per-facade was wrongly
    33 ! calculated leading to unrealistically high energy demands and thus to
    34 ! unreallistically high waste-heat fluxes.
    35 ! 
     33! Major bugfix in calculation of energy demand - floor-area-per-facade was wrongly calculated
     34! leading to unrealistically high energy demands and thus to unreallistically high waste-heat
     35! fluxes.
     36!
    3637! 4346 2019-12-18 11:55:56Z motisi
    37 ! Introduction of wall_flags_total_0, which currently sets bits based on static
    38 ! topography information used in wall_flags_static_0
    39 ! 
     38! Introduction of wall_flags_total_0, which currently sets bits based on static topography
     39! information used in wall_flags_static_0
     40!
    4041! 4329 2019-12-10 15:46:36Z motisi
    4142! Renamed wall_flags_0 to wall_flags_static_0
    42 ! 
     43!
    4344! 4310 2019-11-26 19:01:28Z suehring
    44 ! Remove dt_indoor from namelist input. The indoor model is an hourly-based
    45 ! model, calling it more/less often lead to inaccurate results.
    46 ! 
     45! Remove dt_indoor from namelist input. The indoor model is an hourly-based model, calling it
     46! more/less often lead to inaccurate results.
     47!
    4748! 4299 2019-11-22 10:13:38Z suehring
    48 ! Output of indoor temperature revised (to avoid non-defined values within
    49 ! buildings)
    50 !
     49! Output of indoor temperature revised (to avoid non-defined values within buildings)
     50!
    5151! 4267 2019-10-16 18:58:49Z suehring
    5252! Bugfix in initialization, some indices to access building_pars where wrong.
    5353! Introduction of seasonal parameters.
    54 ! 
     54!
    5555! 4246 2019-09-30 09:27:52Z pavelkrc
    56 ! 
    57 ! 
     56!
     57!
    5858! 4242 2019-09-27 12:59:10Z suehring
    5959! Bugfix in array index
    60 ! 
     60!
    6161! 4238 2019-09-25 16:06:01Z suehring
    6262! - Bugfix in determination of minimum facade height and in location message
    6363! - Bugfix, avoid division by zero
    64 ! - Some optimization 
    65 ! 
     64! - Some optimization
     65!
    6666! 4227 2019-09-10 18:04:34Z gronemeier
    6767! implement new palm_date_time_mod
     
    7272! 4209 2019-09-02 12:00:03Z suehring
    7373! - Bugfix in initialization of indoor temperature
    74 ! - Prescibe default indoor temperature in case it is not given in the
    75 !   namelist input
     74! - Prescibe default indoor temperature in case it is not given in the namelist input
    7675!
    7776! 4182 2019-08-21 14:37:54Z scharf
    7877! Corrected "Former revisions" section
    79 ! 
     78!
    8079! 4148 2019-08-08 11:26:00Z suehring
    81 ! Bugfix in case of non grid-resolved buildings. Further, vertical grid spacing
    82 ! is now considered at the correct level. 
     80! Bugfix in case of non grid-resolved buildings. Further, vertical grid spacing is now considered at
     81! the correct level.
    8382! - change calculation of a_m and c_m
    8483! - change calculation of u-values (use h_es in building array)
     
    9392!   in building array
    9493! - change calculation of q_waste_heat
    95 ! - bugfix in averaging mean indoor temperature 
    96 ! 
     94! - bugfix in averaging mean indoor temperature
     95!
    9796! 3759 2019-02-21 15:53:45Z suehring
    9897! - Calculation of total building volume
    9998! - Several bugfixes
    10099! - Calculation of building height revised
    101 ! 
     100!
    102101! 3745 2019-02-15 18:57:56Z suehring
    103102! - remove building_type from module
    104 ! - initialize parameters for each building individually instead of a bulk
    105 !   initializaion with  identical building type for all
     103! - initialize parameters for each building individually instead of a bulk initializaion with
     104!   identical building type for all
    106105! - output revised
    107106! - add missing _wp
    108107! - some restructuring of variables in building data structure
    109 ! 
     108!
    110109! 3744 2019-02-15 18:38:58Z suehring
    111110! Some interface calls moved to module_interface + cleanup
    112 ! 
     111!
    113112! 3469 2018-10-30 20:05:07Z kanani
    114113! Initial revision (tlang, suehring, kanani, srissman)!
     
    125124! Description:
    126125! ------------
    127 !> <Description of the new module>
    128126!> Module for Indoor Climate Model (ICM)
    129127!> The module is based on the DIN EN ISO 13790 with simplified hour-based procedure.
    130128!> This model is a equivalent circuit diagram of a three-point RC-model (5R1C).
    131 !> This module differ between indoor-air temperature an average temperature of indoor surfaces which make it prossible to determine thermal comfort
    132 !> the heat transfer between indoor and outdoor is simplified
    133 
     129!> This module differs between indoor-air temperature an average temperature of indoor surfaces which make it prossible to determine
     130!> thermal comfort
     131!> the heat transfer between indoor and outdoor is simplified
     132
     133!> @todo Many statement comments that are given as doxygen comments need to be changed to normal comments
    134134!> @todo Replace window_area_per_facade by %frac(1,m) for window
    135 !> @todo emissivity change for window blinds if solar_protection_on=1 
     135!> @todo emissivity change for window blinds if solar_protection_on=1
    136136
    137137!> @note Do we allow use of integer flags, or only logical flags? (concerns e.g. cooling_on, heating_on)
     
    139139!>
    140140!> @bug  <Enter known bugs here>
    141 !------------------------------------------------------------------------------!
    142  MODULE indoor_model_mod 
    143 
    144     USE arrays_3d,                                                             &
    145         ONLY:  ddzw,                                                           &
    146                dzw,                                                            &
     141!--------------------------------------------------------------------------------------------------!
     142 MODULE indoor_model_mod
     143
     144    USE arrays_3d,                                                                                 &
     145        ONLY:  ddzw,                                                                               &
     146               dzw,                                                                                &
    147147               pt
    148148
    149     USE control_parameters,                                                    &
     149    USE control_parameters,                                                                        &
    150150        ONLY:  initializing_actions
    151151
    152152    USE kinds
    153    
    154     USE netcdf_data_input_mod,                                                 &
     153
     154    USE netcdf_data_input_mod,                                                                     &
    155155        ONLY:  building_id_f, building_type_f
    156156
    157     USE palm_date_time_mod,                                                    &
    158         ONLY:  get_date_time, northward_equinox, seconds_per_hour,             &
    159                southward_equinox
    160 
    161     USE surface_mod,                                                           &
     157    USE palm_date_time_mod,                                                                        &
     158        ONLY:  get_date_time, northward_equinox, seconds_per_hour, southward_equinox
     159
     160    USE surface_mod,                                                                               &
    162161        ONLY:  surf_usm_h, surf_usm_v
    163162
     
    170169
    171170       INTEGER(iwp) ::  id                                !< building ID
     171       INTEGER(iwp) ::  kb_max                            !< highest vertical index of a building
    172172       INTEGER(iwp) ::  kb_min                            !< lowest vertical index of a building
    173        INTEGER(iwp) ::  kb_max                            !< highest vertical index of a building
    174173       INTEGER(iwp) ::  num_facades_per_building_h = 0    !< total number of horizontal facades elements
    175174       INTEGER(iwp) ::  num_facades_per_building_h_l = 0  !< number of horizontal facade elements on local subdomain
     
    179178
    180179       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  l_v            !< index array linking surface-element orientation index
    181                                                                   !< for vertical surfaces with building 
     180                                                                  !< for vertical surfaces with building
    182181       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_h            !< index array linking surface-element index for
    183182                                                                  !< horizontal surfaces with building
    184        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_v            !< index array linking surface-element index for 
     183       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  m_v            !< index array linking surface-element index for
    185184                                                                  !< vertical surfaces with building
    186        INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_h   !< number of horizontal facade elements per buidling 
     185       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_h   !< number of horizontal facade elements per buidling
    187186                                                                  !< and height level
    188187       INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facade_v   !< number of vertical facades elements per buidling
    189188                                                                  !< and height level
    190                                                                  
     189
    191190
    192191       LOGICAL ::  on_pe = .FALSE.   !< flag indicating whether a building with certain ID is on local subdomain
    193        
     192
    194193       REAL(wp) ::  air_change_high       !< [1/h] air changes per time_utc_hour
    195194       REAL(wp) ::  air_change_low        !< [1/h] air changes per time_utc_hour
     
    199198       REAL(wp) ::  factor_a              !< [-] Dynamic parameters specific effective surface according to Table 12; 2.5
    200199                                          !< (very light, light and medium), 3.0 (heavy), 3.5 (very heavy)
    201        REAL(wp) ::  factor_c              !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000 
     200       REAL(wp) ::  factor_c              !< [J/(m2 K)] Dynamic parameters inner heatstorage according to Table 12; 80000
    202201                                          !< (very light), 110000 (light), 165000 (medium), 260000 (heavy), 370000 (very heavy)
    203202       REAL(wp) ::  f_c_win               !< [-] shading factor
    204203       REAL(wp) ::  fapf                  !< [m2/m2] floor area per facade
    205204       REAL(wp) ::  g_value_win           !< [-] SHGC factor
    206        REAL(wp) ::  h_es                  !< [W/(m2 K)] surface-related heat transfer coefficient between extern and surface 
     205       REAL(wp) ::  h_es                  !< [W/(m2 K)] surface-related heat transfer coefficient between extern and surface
    207206       REAL(wp) ::  height_cei_con        !< [m] ceiling construction heigth
    208207       REAL(wp) ::  height_storey         !< [m] storey heigth
    209208       REAL(wp) ::  params_waste_heat_c   !< [-] anthropogenic heat outputs for cooling e.g. 1.33 for KKM with COP = 3
    210        REAL(wp) ::  params_waste_heat_h   !< [-] anthropogenic heat outputs for heating e.g. 1 - 0.9 = 0.1 for combustion with eta = 0.9 or -2 for WP with COP = 3
     209       REAL(wp) ::  params_waste_heat_h   !< [-] anthropogenic heat outputs for heating e.g. 1 - 0.9 = 0.1 for combustion with
     210                                          !< eta = 0.9 or -2 for WP with COP = 3
    211211       REAL(wp) ::  phi_c_max             !< [W] Max. Cooling capacity (negative)
    212212       REAL(wp) ::  phi_h_max             !< [W] Max. Heating capacity (positive)
     
    229229       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vol_frac   !< fraction of local on total building volume, height dependent
    230230       REAL(wp), DIMENSION(:), ALLOCATABLE ::  vpf        !< building volume volume per facade element, height dependent
    231        
     231
    232232    END TYPE build
    233233
     
    237237!
    238238!-- Declare all global variables within the module
     239
     240    REAL(wp), PARAMETER ::  dt_indoor = 3600.0_wp                  !< [s] time interval for indoor-model application, fixed to
     241                                                                   !< 3600.0 due to model requirements
     242    REAL(wp), PARAMETER ::  h_is                     = 3.45_wp     !< [W/(m2 K)] surface-related heat transfer coefficient between
     243                                                                   !< surface and air (chap. 7.2.2.2)
     244    REAL(wp), PARAMETER ::  h_ms                     = 9.1_wp      !< [W/(m2 K)] surface-related heat transfer coefficient between
     245                                                                   !< component and surface (chap. 12.2.2)
     246    REAL(wp), PARAMETER ::  params_f_f               = 0.3_wp      !< [-] frame ratio chap. 8.3.2.1.1 for buildings with mostly
     247                                                                   !< cooling 2.0_wp
     248    REAL(wp), PARAMETER ::  params_f_w               = 0.9_wp      !< [-] correction factor (fuer nicht senkrechten Stahlungseinfall
     249                                                                   !< DIN 4108-2 chap.8, (hier konstant, keine WinkelabhÀngigkeit)
     250    REAL(wp), PARAMETER ::  params_f_win             = 0.5_wp      !< [-] proportion of window area, Database A_win aus
     251                                                                   !< Datenbank 27 window_area_per_facade_percent
     252    REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation
     253                                                                   !< on facade exceeds this value
     254
    239255    INTEGER(iwp) ::  cooling_on              !< Indoor cooling flag (0=off, 1=on)
    240256    INTEGER(iwp) ::  heating_on              !< Indoor heating flag (0=off, 1=on)
     
    242258    INTEGER(iwp) ::  solar_protection_on     !< Solar protection on
    243259
    244     REAL(wp), PARAMETER ::  dt_indoor = 3600.0_wp    !< [s] time interval for indoor-model application, fixed to 3600.0 due to model requirements
    245260
    246261    REAL(wp) ::  a_m                                 !< [m2] the effective mass-related area
     
    251266    REAL(wp) ::  h_t_1                               !< [W/K] Heat transfer coefficient auxiliary variable 1
    252267    REAL(wp) ::  h_t_2                               !< [W/K] Heat transfer coefficient auxiliary variable 2
    253     REAL(wp) ::  h_t_3                               !< [W/K] Heat transfer coefficient auxiliary variable 3
    254     REAL(wp) ::  h_t_wm                              !< [W/K] Heat transfer coefficient of the emmision (got with h_t_ms the thermal mass)
     268    REAL(wp) ::  h_t_3                               !< [W/K] Heat transfer coefficient auxiliary variable 3
     269    REAL(wp) ::  h_t_es                              !< [W/K] heat transfer coefficient of doors, windows, curtain walls and
     270                                                     !< glazed walls (assumption: thermal mass=0)
    255271    REAL(wp) ::  h_t_is                              !< [W/K] thermal coupling conductance (Thermischer Kopplungsleitwert)
    256272    REAL(wp) ::  h_t_ms                              !< [W/K] Heat transfer conductance term (got with h_t_wm the thermal mass)
    257273    REAL(wp) ::  h_t_wall                            !< [W/K] heat transfer coefficient of opaque components (assumption: got all
    258274                                                     !< thermal mass) contains of h_t_wm and h_t_ms
    259     REAL(wp) ::  h_t_es                              !< [W/K] heat transfer coefficient of doors, windows, curtain walls and
    260                                                      !< glazed walls (assumption: thermal mass=0)
     275    REAL(wp) ::  h_t_wm                              !< [W/K] Heat transfer coefficient of the emmision (got with h_t_ms the
     276                                                     !< thermal mass)
    261277    REAL(wp) ::  h_v                                 !< [W/K] heat transfer of ventilation
    262278    REAL(wp) ::  indoor_volume_per_facade            !< [m3] indoor air volume per facade element
     
    264280    REAL(wp) ::  net_sw_in                           !< [W/m2] net short-wave radiation
    265281    REAL(wp) ::  phi_hc_nd                           !< [W] heating demand and/or cooling demand
    266     REAL(wp) ::  phi_hc_nd_10                        !< [W] heating demand and/or cooling demand for heating or cooling 
     282    REAL(wp) ::  phi_hc_nd_10                        !< [W] heating demand and/or cooling demand for heating or cooling
    267283    REAL(wp) ::  phi_hc_nd_ac                        !< [W] actual heating demand and/or cooling demand
    268284    REAL(wp) ::  phi_hc_nd_un                        !< [W] unlimited heating demand and/or cooling demand which is necessary to
    269                                                      !< reach the demanded required temperature (heating is positive, 
    270                                                      !< cooling is negative) 
     285                                                     !< reach the demanded required temperature (heating is positive,
     286                                                     !< cooling is negative)
    271287    REAL(wp) ::  phi_ia                              !< [W] internal air load = internal loads * 0.5, Eq. (C.1)
    272288    REAL(wp) ::  phi_m                               !< [W] mass specific thermal load (internal and external)
    273289    REAL(wp) ::  phi_mtot                            !< [W] total mass specific thermal load (internal and external)
    274290    REAL(wp) ::  phi_sol                             !< [W] solar loads
    275     REAL(wp) ::  phi_st                              !< [W] mass specific thermal load implied non thermal mass 
     291    REAL(wp) ::  phi_st                              !< [W] mass specific thermal load implied non thermal mass
    276292    REAL(wp) ::  q_wall_win                          !< [W/m2]heat flux from indoor into wall/window
    277293    REAL(wp) ::  q_waste_heat                        !< [W/m2]waste heat, sum of waste heat over the roof to Palm
    278                                                      
     294
    279295    REAL(wp) ::  q_c_m                               !< [W] Energy of thermal storage mass specific thermal load for internal
    280296                                                     !< and external heatsources (for energy bilanz)
    281     REAL(wp) ::  q_c_st                              !< [W] Energy of thermal storage mass specific thermal load implied non thermal mass (for energy bilanz)
     297    REAL(wp) ::  q_c_st                              !< [W] Energy of thermal storage mass specific thermal load implied non
     298                                                     !< thermal mass (for energy bilanz)
    282299    REAL(wp) ::  q_int                               !< [W] Energy of internal air load (for energy bilanz)
    283300    REAL(wp) ::  q_sol                               !< [W] Energy of solar (for energy bilanz)
    284301    REAL(wp) ::  q_trans                             !< [W] Energy of transmission (for energy bilanz)
    285302    REAL(wp) ::  q_vent                              !< [W] Energy of ventilation (for energy bilanz)
    286                                                      
     303
    287304    REAL(wp) ::  schedule_d                          !< [-] activation for internal loads (low or high + low)
    288305    REAL(wp) ::  skip_time_do_indoor = 0.0_wp        !< [s] Indoor model is not called before this time
    289306    REAL(wp) ::  theta_air                           !< [degree_C] air temperature of the RC-node
    290307    REAL(wp) ::  theta_air_0                         !< [degree_C] air temperature of the RC-node in equilibrium
    291     REAL(wp) ::  theta_air_10                        !< [degree_C] air temperature of the RC-node from a heating capacity 
     308    REAL(wp) ::  theta_air_10                        !< [degree_C] air temperature of the RC-node from a heating capacity
    292309                                                     !< of 10 W/m2
    293310    REAL(wp) ::  theta_air_ac                        !< [degree_C] actual room temperature after heating/cooling
     
    301318    REAL(wp) ::  total_area                          !< [m2] area of all surfaces pointing to zone
    302319    REAL(wp) ::  window_area_per_facade              !< [m2] window area per facade element
    303    
    304     REAL(wp), PARAMETER ::  h_is                     = 3.45_wp     !< [W/(m2 K)] surface-related heat transfer coefficient between
    305                                                                    !< surface and air (chap. 7.2.2.2)
    306     REAL(wp), PARAMETER ::  h_ms                     = 9.1_wp      !< [W/(m2 K)] surface-related heat transfer coefficient between component and surface (chap. 12.2.2)
    307     REAL(wp), PARAMETER ::  params_f_f               = 0.3_wp      !< [-] frame ratio chap. 8.3.2.1.1 for buildings with mostly cooling 2.0_wp
    308     REAL(wp), PARAMETER ::  params_f_w               = 0.9_wp      !< [-] correction factor (fuer nicht senkrechten Stahlungseinfall
    309                                                                    !< DIN 4108-2 chap.8, (hier konstant, keine WinkelabhÀngigkeit)
    310     REAL(wp), PARAMETER ::  params_f_win             = 0.5_wp      !< [-] proportion of window area, Database A_win aus
    311                                                                    !< Datenbank 27 window_area_per_facade_percent
    312     REAL(wp), PARAMETER ::  params_solar_protection  = 300.0_wp    !< [W/m2] chap. G.5.3.1 sun protection closed, if the radiation
    313                                                                    !< on facade exceeds this value
     320
    314321!
    315322!-- Definition of seasonal parameters, summer and winter, for different building types
    316     REAL(wp), DIMENSION(0:1,1:7) ::  summer_pars = RESHAPE( (/               & ! building_type 1
    317                                           0.5_wp,                              & ! basical airflow without occupancy of the room
    318                                           2.0_wp,                              & ! additional airflow depend of occupancy of the room
    319                                           0.5_wp,                              & ! building_type 2: basical airflow without occupancy of the room
    320                                           2.0_wp,                              & ! additional airflow depend of occupancy of the room
    321                                           0.8_wp,                              & ! building_type 3: basical airflow without occupancy of the room
    322                                           2.0_wp,                              & ! additional airflow depend of occupancy of the room
    323                                           0.1_wp,                              & ! building_type 4: basical airflow without occupancy of the room
    324                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    325                                           0.1_wp,                              & ! building_type 5: basical airflow without occupancy of the room
    326                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    327                                           0.1_wp,                              & ! building_type 6: basical airflow without occupancy of the room
    328                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    329                                           0.1_wp,                              & ! building_type 7: basical airflow without occupancy of the room
    330                                           1.5_wp                               & ! additional airflow depend of occupancy of the room
     323    REAL(wp), DIMENSION(0:1,1:7) ::  summer_pars = RESHAPE( (/                & ! building_type 1
     324                                          0.5_wp,                             & ! basical airflow without occupancy of the room
     325                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
     326                                          0.5_wp,                             & ! building_type 2: basical airflow without occupancy
     327                                                                                ! of the room
     328                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
     329                                          0.8_wp,                             & ! building_type 3: basical airflow without occupancy
     330                                                                                ! of the room
     331                                          2.0_wp,                             & ! additional airflow depend of occupancy of the room
     332                                          0.1_wp,                             & ! building_type 4: basical airflow without occupancy
     333                                                                                ! of the room
     334                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     335                                          0.1_wp,                             & ! building_type 5: basical airflow without occupancy
     336                                                                                ! of the room
     337                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     338                                          0.1_wp,                             & ! building_type 6: basical airflow without occupancy
     339                                                                                ! of the room
     340                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     341                                          0.1_wp,                             & ! building_type 7: basical airflow without occupancy
     342                                                                                ! of the room
     343                                          1.5_wp                              & ! additional airflow depend of occupancy of the room
    331344                                                           /), (/ 2, 7 /) )
    332345
    333     REAL(wp), DIMENSION(0:1,1:7) ::  winter_pars = RESHAPE( (/               & ! building_type 1
    334                                           0.1_wp,                              & ! basical airflow without occupancy of the room
    335                                           0.5_wp,                              & ! additional airflow depend of occupancy of the room
    336                                           0.1_wp,                              & ! building_type 2: basical airflow without occupancy of the room
    337                                           0.5_wp,                              & ! additional airflow depend of occupancy of the room
    338                                           0.1_wp,                              & ! building_type 3: basical airflow without occupancy of the room
    339                                           0.5_wp,                              & ! additional airflow depend of occupancy of the room
    340                                           0.1_wp,                              & ! building_type 4: basical airflow without occupancy of the room
    341                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    342                                           0.1_wp,                              & ! building_type 5: basical airflow without occupancy of the room
    343                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    344                                           0.1_wp,                              & ! building_type 6: basical airflow without occupancy of the room
    345                                           1.5_wp,                              & ! additional airflow depend of occupancy of the room
    346                                           0.1_wp,                              & ! building_type 7: basical airflow without occupancy of the room
    347                                           1.5_wp                               & ! additional airflow depend of occupancy of the room
     346    REAL(wp), DIMENSION(0:1,1:7) ::  winter_pars = RESHAPE( (/                & ! building_type 1
     347                                          0.1_wp,                             & ! basical airflow without occupancy of the room
     348                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
     349                                          0.1_wp,                             & ! building_type 2: basical airflow without occupancy
     350                                                                                ! of the room
     351                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
     352                                          0.1_wp,                             & ! building_type 3: basical airflow without occupancy
     353                                                                                ! of the room
     354                                          0.5_wp,                             & ! additional airflow depend of occupancy of the room
     355                                          0.1_wp,                             & ! building_type 4: basical airflow without occupancy
     356                                                                                ! of the room
     357                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     358                                          0.1_wp,                             & ! building_type 5: basical airflow without occupancy
     359                                                                                ! of the room
     360                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     361                                          0.1_wp,                             & ! building_type 6: basical airflow without occupancy
     362                                                                                ! of the room
     363                                          1.5_wp,                             & ! additional airflow depend of occupancy of the room
     364                                          0.1_wp,                             & ! building_type 7: basical airflow without occupancy
     365                                                                                ! of the room
     366                                          1.5_wp                              & ! additional airflow depend of occupancy of the room
    348367                                                           /), (/ 2, 7 /) )
    349368
     
    352371
    353372    PRIVATE
    354    
     373
    355374!
    356375!-- Add INTERFACES that must be available to other modules
    357     PUBLIC im_init, im_main_heatcool, im_parin, im_define_netcdf_grid,          &
    358            im_check_data_output, im_data_output_3d, im_check_parameters
    359    
     376    PUBLIC im_init, im_main_heatcool, im_parin, im_define_netcdf_grid, im_check_data_output,       &
     377           im_data_output_3d, im_check_parameters
     378
    360379
    361380!
     
    385404        MODULE PROCEDURE im_define_netcdf_grid
    386405     END INTERFACE im_define_netcdf_grid
    387 ! 
     406!
    388407! !
    389408! !-- Output of information to the header file
     
    392411!     END INTERFACE im_header
    393412!
    394 !-- Calculations for indoor temperatures 
     413!-- Calculations for indoor temperatures
    395414    INTERFACE im_calc_temperatures
    396415       MODULE PROCEDURE im_calc_temperatures
    397416    END INTERFACE im_calc_temperatures
    398417!
    399 !-- Initialization actions 
     418!-- Initialization actions
    400419    INTERFACE im_init
    401420       MODULE PROCEDURE im_init
    402421    END INTERFACE im_init
    403422!
    404 !-- Main part of indoor model 
     423!-- Main part of indoor model
    405424    INTERFACE im_main_heatcool
    406425       MODULE PROCEDURE im_main_heatcool
     
    414433 CONTAINS
    415434
    416 !------------------------------------------------------------------------------!
     435!--------------------------------------------------------------------------------------------------!
    417436! Description:
    418437! ------------
    419 !< Calculation of the air temperatures and mean radiation temperature
    420 !< This is basis for the operative temperature
    421 !< Based on a Crank-Nicholson scheme with a timestep of a hour
    422 !------------------------------------------------------------------------------!
    423  SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,    &
     438!< Calculation of the air temperatures and mean radiation temperature.
     439!< This is basis for the operative temperature.
     440!< Based on a Crank-Nicholson scheme with a timestep of a hour.
     441!--------------------------------------------------------------------------------------------------!
     442 SUBROUTINE im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                        &
    424443                                   near_facade_temperature, phi_hc_nd_dummy )
    425444
     
    427446    INTEGER(iwp) ::  j
    428447    INTEGER(iwp) ::  k
    429    
     448
    430449    REAL(wp) ::  indoor_wall_window_temperature  !< weighted temperature of innermost wall/window layer
    431450    REAL(wp) ::  near_facade_temperature
     
    433452!
    434453!-- Calculation of total mass specific thermal load (internal and external)
    435     phi_mtot = ( phi_m + h_t_wm * indoor_wall_window_temperature               &
    436                        + h_t_3  * ( phi_st + h_t_es * pt(k,j,i)                &
    437                                             + h_t_1 *                          &
    438                                     ( ( ( phi_ia + phi_hc_nd_dummy ) / h_v )   &
    439                                                  + near_facade_temperature )   &
    440                                    ) / h_t_2                                   &
     454    phi_mtot = ( phi_m + h_t_wm * indoor_wall_window_temperature                                   &
     455                       + h_t_3  * ( phi_st + h_t_es * pt(k,j,i)                                    &
     456                                            + h_t_1 *                                              &
     457                                    ( ( ( phi_ia + phi_hc_nd_dummy ) / h_v )                       &
     458                                                 + near_facade_temperature )                       &
     459                                  ) / h_t_2                                                        &
    441460               )                                                                !< [degree_C] Eq. (C.5)
    442 ! 
     461!
    443462!-- Calculation of component temperature at factual timestep
    444     theta_m_t = ( ( theta_m_t_prev                                             &
    445                     * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_t_3 + h_t_wm ) )    &
    446                      + phi_mtot                                                &
    447                   )                                                            &
    448                   /   ( ( c_m / 3600.0_wp ) + 0.5_wp * ( h_t_3 + h_t_wm ) )    &
     463    theta_m_t = ( ( theta_m_t_prev                                                                 &
     464                    * ( ( c_m / 3600.0_wp ) - 0.5_wp * ( h_t_3 + h_t_wm ) )                        &
     465                     + phi_mtot                                                                    &
     466                  )                                                                                &
     467                  /   ( ( c_m / 3600.0_wp ) + 0.5_wp * ( h_t_3 + h_t_wm ) )                        &
    449468                )                                                               !< [degree_C] Eq. (C.4)
    450469!
    451470!-- Calculation of mean inner temperature for the RC-node in actual timestep
    452471    theta_m = ( theta_m_t + theta_m_t_prev ) * 0.5_wp                           !< [degree_C] Eq. (C.9)
    453    
     472
    454473!
    455474!-- Calculation of mean surface temperature of the RC-node in actual timestep
    456     theta_s = ( (   h_t_ms * theta_m + phi_st + h_t_es * pt(k,j,i)             &
    457                   + h_t_1  * ( near_facade_temperature                         &
    458                            + ( phi_ia + phi_hc_nd_dummy ) / h_v )              &
    459                 )                                                              &
    460                 / ( h_t_ms + h_t_es + h_t_1 )                                  &
     475    theta_s = ( (   h_t_ms * theta_m + phi_st + h_t_es * pt(k,j,i)                                 &
     476                  + h_t_1  * ( near_facade_temperature                                             &
     477                           + ( phi_ia + phi_hc_nd_dummy ) / h_v )                                  &
     478                )                                                                                  &
     479                / ( h_t_ms + h_t_es + h_t_1 )                                                      &
    461480              )                                                                 !< [degree_C] Eq. (C.10)
    462    
     481
    463482!
    464483!-- Calculation of the air temperature of the RC-node
    465     theta_air = ( h_t_is * theta_s + h_v * near_facade_temperature             &
    466                 + phi_ia + phi_hc_nd_dummy ) / ( h_t_is + h_v )                 !< [degree_C] Eq. (C.11)
     484    theta_air = ( h_t_is * theta_s + h_v * near_facade_temperature + phi_ia + phi_hc_nd_dummy ) /  &
     485                ( h_t_is + h_v )                                                !< [degree_C] Eq. (C.11)
    467486
    468487 END SUBROUTINE im_calc_temperatures
    469488
    470 !------------------------------------------------------------------------------!
     489
     490!--------------------------------------------------------------------------------------------------!
    471491! Description:
    472492! ------------
    473493!> Initialization of the indoor model.
    474 !> Static information are calculated here, e.g. building parameters and
    475 !> geometrical information, everything that doesn't change in time.
     494!> Static information are calculated here, e.g. building parameters and geometrical information,
     495!> anything that doesn't change in time.
    476496!
    477497!-- Input values
     
    480500!     theta_e              -->  pt(k,j,i)                         !< undisturbed outside temperature, 1. PALM volume, for windows
    481501!     theta_sup = theta_f  -->  surf_usm_h%pt_10cm(m)
    482 !                               surf_usm_v(l)%pt_10cm(m)          !< Air temperature, facade near (10cm) air temperature from 1. Palm volume
     502!                               surf_usm_v(l)%pt_10cm(m)          !< Air temperature, facade near (10cm) air temperature from
     503                                                                  !< 1. Palm volume
    483504!     theta_node           -->  t_wall_h(nzt_wall,m)
    484505!                               t_wall_v(l)%t(nzt_wall,m)         !< Temperature of innermost wall layer, for opaque wall
    485 !------------------------------------------------------------------------------!
     506!--------------------------------------------------------------------------------------------------!
    486507 SUBROUTINE im_init
    487508
    488     USE control_parameters,                                                    &
     509    USE control_parameters,                                                                        &
    489510        ONLY:  message_string, time_since_reference_point
    490511
    491     USE indices,                                                               &
     512    USE indices,                                                                                   &
    492513        ONLY:  nxl, nxr, nyn, nys, nzb, nzt, wall_flags_total_0
    493514
    494     USE grid_variables,                                                        &
     515    USE grid_variables,                                                                            &
    495516        ONLY:  dx, dy
    496517
    497518    USE pegrid
    498519
    499     USE surface_mod,                                                           &
     520    USE surface_mod,                                                                               &
    500521        ONLY:  surf_usm_h, surf_usm_v
    501        
    502     USE urban_surface_mod,                                                     &
     522
     523    USE urban_surface_mod,                                                                         &
    503524        ONLY:  building_pars, building_type
    504525
     
    514535
    515536    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids           !< building IDs on entire model domain
    516     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain, 
    517                                                                     !< multiple occurences are sorted out 
     537    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final     !< building IDs on entire model domain,
     538                                                                    !< multiple occurences are sorted out
    518539    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_final_tmp !< temporary array used for resizing
    519540    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  build_ids_l         !< building IDs on local subdomain
     
    523544    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  k_min_l             !< lowest vertical index of a building on subdomain
    524545    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  n_fa                !< counting array
    525     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_h       !< dummy array used for summing-up total number of 
     546    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_h       !< dummy array used for summing-up total number of
    526547                                                                    !< horizontal facade elements
    527     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_v       !< dummy array used for summing-up total number of 
     548    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  num_facades_v       !< dummy array used for summing-up total number of
    528549                                                                    !< vertical facade elements
    529     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_h       !< dummy array used for MPI_ALLREDUCE 
    530     INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_v       !< dummy array used for MPI_ALLREDUCE 
    531    
     550    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_h       !< dummy array used for MPI_ALLREDUCE
     551    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  receive_dum_v       !< dummy array used for MPI_ALLREDUCE
     552
    532553    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings         !< number of buildings with different ID on entire model domain
    533554    INTEGER(iwp), DIMENSION(0:numprocs-1) ::  num_buildings_l       !< number of buildings with different ID on local subdomain
    534                                                              
     555
    535556    REAL(wp) ::  u_tmp                                     !< dummy for temporary calculation of u-value without h_is
    536557    REAL(wp) ::  du_tmp                                    !< 1/u_tmp
     
    544565    CALL location_message( 'initializing indoor model', 'start' )
    545566!
    546 !-- Initializing of indoor model is only possible if buildings can be
    547 !-- distinguished by their IDs.
     567!-- Initializing of indoor model is only possible if buildings can be distinguished by their IDs.
    548568    IF ( .NOT. building_id_f%from_file )  THEN
    549569       message_string = 'Indoor model requires information about building_id'
     
    559579          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    560580             IF ( num_buildings_l(myid) > 0 )  THEN
    561                 IF ( ANY( building_id_f%var(j,i) .EQ.  build_ids_l ) )  THEN
     581                IF ( ANY( building_id_f%var(j,i) == build_ids_l ) )  THEN
    562582                   CYCLE
    563583                ELSE
     
    569589                   DEALLOCATE( build_ids_l )
    570590                   ALLOCATE( build_ids_l(1:num_buildings_l(myid)) )
    571                    build_ids_l(1:num_buildings_l(myid)-1) =                 &
    572                                build_ids_l_tmp(1:num_buildings_l(myid)-1)
     591                   build_ids_l(1:num_buildings_l(myid)-1) =                                        &
     592                                                          build_ids_l_tmp(1:num_buildings_l(myid)-1)
    573593                   build_ids_l(num_buildings_l(myid)) = building_id_f%var(j,i)
    574594                   DEALLOCATE( build_ids_l_tmp )
    575595                ENDIF
    576596!
    577 !--          First occuring building id on PE 
    578              ELSE 
     597!--          First occuring building id on PE
     598             ELSE
    579599                num_buildings_l(myid) = num_buildings_l(myid) + 1
    580600                build_ids_l(1) = building_id_f%var(j,i)
     
    584604    ENDDO
    585605!
    586 !-- Determine number of building IDs for the entire domain. (Note, building IDs
    587 !-- can appear multiple times as buildings might be distributed over several
    588 !-- PEs.)
    589 #if defined( __parallel )
    590     CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs,              &
    591                         MPI_INTEGER, MPI_SUM, comm2d, ierr )
     606!-- Determine number of building IDs for the entire domain. (Note, building IDs can appear multiple
     607!-- times as buildings might be distributed over several PEs.)
     608#if defined( __parallel )
     609    CALL MPI_ALLREDUCE( num_buildings_l, num_buildings, numprocs, MPI_INTEGER, MPI_SUM, comm2d,    &
     610                        ierr )
    592611#else
    593612    num_buildings = num_buildings_l
     
    595614    ALLOCATE( build_ids(1:SUM(num_buildings)) )
    596615!
    597 !-- Gather building IDs. Therefore, first, determine displacements used
    598 !-- required for MPI_GATHERV call.
     616!-- Gather building IDs. Therefore, first, determine displacements used required for MPI_GATHERV
     617!-- call.
    599618    ALLOCATE( displace_dum(0:numprocs-1) )
    600619    displace_dum(0) = 0
     
    603622    ENDDO
    604623
    605 #if defined( __parallel ) 
    606     CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                 &
    607                          num_buildings(myid),                                  &
    608                          MPI_INTEGER,                                          &
    609                          build_ids,                                            &
    610                          num_buildings,                                        &
    611                          displace_dum,                                         &
    612                          MPI_INTEGER,                                          &
    613                          comm2d, ierr )   
     624#if defined( __parallel )
     625    CALL MPI_ALLGATHERV( build_ids_l(1:num_buildings_l(myid)),                                     &
     626                         num_buildings(myid),                                                      &
     627                         MPI_INTEGER,                                                              &
     628                         build_ids,                                                                &
     629                         num_buildings,                                                            &
     630                         displace_dum,                                                             &
     631                         MPI_INTEGER,                                                              &
     632                         comm2d, ierr )
    614633
    615634    DEALLOCATE( displace_dum )
     
    619638#endif
    620639!
    621 !-- Note: in parallel mode, building IDs can occur mutliple times, as
    622 !-- each PE has send its own ids. Therefore, sort out building IDs which
    623 !-- appear multiple times.
     640!-- Note: in parallel mode, building IDs can occur mutliple times, as each PE has send its own ids.
     641!-- Therefore, sort out building IDs which appear multiple times.
    624642    num_build = 0
    625643    DO  n = 1, SIZE(build_ids)
     
    639657             build_ids_final(num_build) = build_ids(n)
    640658             DEALLOCATE( build_ids_final_tmp )
    641           ENDIF             
     659          ENDIF
    642660       ELSE
    643661          num_build = num_build + 1
     
    648666
    649667!
    650 !-- Allocate building-data structure array. Note, this is a global array
    651 !-- and all building IDs on domain are known by each PE. Further attributes,
    652 !-- e.g. height-dependent arrays, however, are only allocated on PEs where
    653 !-- the respective building is present (in order to reduce memory demands).
     668!-- Allocate building-data structure array. Note, this is a global array and all building IDs on
     669!-- domain are known by each PE. Further attributes, e.g. height-dependent arrays, however, are only
     670!-- allocated on PEs where  the respective building is present (in order to reduce memory demands).
    654671    ALLOCATE( buildings(1:num_build) )
    655672
    656673!
    657 !-- Store building IDs and check if building with certain ID is present on
    658 !-- subdomain.
     674!-- Store building IDs and check if building with certain ID is present on subdomain.
    659675    DO  nb = 1, num_build
    660676       buildings(nb)%id = build_ids_final(nb)
    661677
    662        IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )    &
     678       IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )                        &
    663679          buildings(nb)%on_pe = .TRUE.
    664     ENDDO 
    665 !
    666 !-- Determine the maximum vertical dimension occupied by each building. 
     680    ENDDO
     681!
     682!-- Determine the maximum vertical dimension occupied by each building.
    667683    ALLOCATE( k_min_l(1:num_build) )
    668684    ALLOCATE( k_max_l(1:num_build) )
    669685    k_min_l = nzt + 1
    670     k_max_l = 0   
     686    k_max_l = 0
    671687
    672688    DO  i = nxl, nxr
    673689       DO  j = nys, nyn
    674690          IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    675              nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),    &
    676                          DIM = 1 )
     691             nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    677692             DO  k = nzb, nzt+1
    678693!
    679 !--             Check if grid point belongs to a building. 
     694!--             Check if grid point belongs to a building.
    680695                IF ( BTEST( wall_flags_total_0(k,j,i), 6 ) )  THEN
    681696                   k_min_l(nb) = MIN( k_min_l(nb), k )
     
    688703    ENDDO
    689704
    690 #if defined( __parallel ) 
    691     CALL MPI_ALLREDUCE( k_min_l(:), buildings(:)%kb_min, num_build,            &
    692                         MPI_INTEGER, MPI_MIN, comm2d, ierr )
    693     CALL MPI_ALLREDUCE( k_max_l(:), buildings(:)%kb_max, num_build,            &
    694                         MPI_INTEGER, MPI_MAX, comm2d, ierr )
     705#if defined( __parallel )
     706    CALL MPI_ALLREDUCE( k_min_l(:), buildings(:)%kb_min, num_build, MPI_INTEGER, MPI_MIN, comm2d,  &
     707                        ierr )
     708    CALL MPI_ALLREDUCE( k_max_l(:), buildings(:)%kb_max, num_build, MPI_INTEGER, MPI_MAX, comm2d,  &
     709                        ierr )
    695710#else
    696711    buildings(:)%kb_min = k_min_l(:)
     
    705720       buildings(nb)%building_height = 0.0_wp
    706721       DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    707           buildings(nb)%building_height = buildings(nb)%building_height        &
    708                                         + dzw(k+1)
     722          buildings(nb)%building_height = buildings(nb)%building_height + dzw(k+1)
    709723       ENDDO
    710724    ENDDO
     
    719733       volume_l = 0.0_wp
    720734!
    721 !--    Calculate building volume per height level on each PE where
    722 !--    these building is present.
     735!--    Calculate building volume per height level on each PE where these building is present.
    723736       IF ( buildings(nb)%on_pe )  THEN
    724737
     
    727740          buildings(nb)%volume   = 0.0_wp
    728741          buildings(nb)%vol_frac = 0.0_wp
    729          
    730           IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) ) &
    731           THEN
     742
     743          IF ( ANY( building_id_f%var(nys:nyn,nxl:nxr) == buildings(nb)%id ) )  THEN
    732744             DO  i = nxl, nxr
    733745                DO  j = nys, nyn
    734746                   DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    735                       IF ( building_id_f%var(j,i) /= building_id_f%fill )      &
     747                      IF ( building_id_f%var(j,i) /= building_id_f%fill )                          &
    736748                         volume_l(k) = volume_l(k) + dx * dy * dzw(k+1)
    737749                   ENDDO
     
    742754!
    743755!--    Sum-up building volume from all subdomains
    744 #if defined( __parallel )
    745        CALL MPI_ALLREDUCE( volume_l, volume, SIZE(volume), MPI_REAL, MPI_SUM,  &
    746                            comm2d, ierr )
     756#if defined( __parallel )
     757       CALL MPI_ALLREDUCE( volume_l, volume, SIZE(volume), MPI_REAL, MPI_SUM, comm2d, ierr )
    747758#else
    748759       volume = volume_l
    749760#endif
    750761!
    751 !--    Save total building volume as well as local fraction on volume on
    752 !--    building data structure.
     762!--    Save total building volume as well as local fraction on volume on building data structure.
    753763       IF ( ALLOCATED( buildings(nb)%volume ) )  buildings(nb)%volume = volume
    754764!
     
    757767!
    758768!--    Calculate total building volume
    759        IF ( ALLOCATED( buildings(nb)%volume ) )                                &
    760           buildings(nb)%vol_tot = SUM( buildings(nb)%volume )
     769       IF ( ALLOCATED( buildings(nb)%volume ) )  buildings(nb)%vol_tot = SUM( buildings(nb)%volume )
    761770
    762771       DEALLOCATE( volume   )
     
    765774    ENDDO
    766775!
    767 !-- Allocate arrays for indoor temperature. 
     776!-- Allocate arrays for indoor temperature.
    768777    DO  nb = 1, num_build
    769778       IF ( buildings(nb)%on_pe )  THEN
     
    775784    ENDDO
    776785!
    777 !-- Allocate arrays for number of facades per height level. Distinguish between
    778 !-- horizontal and vertical facades.
     786!-- Allocate arrays for number of facades per height level. Distinguish between horizontal and
     787!-- vertical facades.
    779788    DO  nb = 1, num_build
    780789       IF ( buildings(nb)%on_pe )  THEN
     
    795804!
    796805!--    For the current facade element determine corresponding building index.
    797 !--    First, obtain j,j,k indices of the building. Please note the
    798 !--    offset between facade/surface element and building location (for
    799 !--    horizontal surface elements the horizontal offsets are zero).
     806!--    First, obtain j,j,k indices of the building. Please note the offset between facade/surface
     807!--    element and building location (for horizontal surface elements the horizontal offsets are
     808!--    zero).
    800809       i = surf_usm_h%i(m) + surf_usm_h%ioff
    801810       j = surf_usm_h%j(m) + surf_usm_h%joff
    802811       k = surf_usm_h%k(m) + surf_usm_h%koff
    803812!
    804 !--    Determine building index and check whether building is on PE
    805        nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
     813!--    Determine building index and check whether building is on PE.
     814       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    806815
    807816       IF ( buildings(nb)%on_pe )  THEN
    808817!
    809818!--       Count number of facade elements at each height level.
    810           buildings(nb)%num_facade_h(k) = buildings(nb)%num_facade_h(k) + 1 
     819          buildings(nb)%num_facade_h(k) = buildings(nb)%num_facade_h(k) + 1
    811820!
    812821!--       Moreover, sum up number of local facade elements per building.
    813           buildings(nb)%num_facades_per_building_h_l =                         &
    814                                 buildings(nb)%num_facades_per_building_h_l + 1
     822          buildings(nb)%num_facades_per_building_h_l =                                             &
     823                                                      buildings(nb)%num_facades_per_building_h_l + 1
    815824       ENDIF
    816825    ENDDO
     
    822831!
    823832!--       For the current facade element determine corresponding building index.
    824 !--       First, obtain j,j,k indices of the building. Please note the
    825 !--       offset between facade/surface element and building location (for
    826 !--       vertical surface elements the vertical offsets are zero).
     833!--       First, obtain j,j,k indices of the building. Please note the offset between facade/surface
     834!--       element and building location (for vertical surface elements the vertical offsets are
     835!--       zero).
    827836          i = surf_usm_v(l)%i(m) + surf_usm_v(l)%ioff
    828837          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
    829838          k = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
    830839
    831           nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),        &
    832                        DIM = 1 )
     840          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    833841          IF ( buildings(nb)%on_pe )  THEN
    834              buildings(nb)%num_facade_v(k) = buildings(nb)%num_facade_v(k) + 1 
    835              buildings(nb)%num_facades_per_building_v_l =                      &
    836                                 buildings(nb)%num_facades_per_building_v_l + 1
     842             buildings(nb)%num_facade_v(k) = buildings(nb)%num_facade_v(k) + 1
     843             buildings(nb)%num_facades_per_building_v_l =                                          &
     844                                                      buildings(nb)%num_facades_per_building_v_l + 1
    837845          ENDIF
    838846       ENDDO
    839847    ENDDO
    840848!
    841 !-- Determine total number of facade elements per building and assign number to
    842 !-- building data type.
     849!-- Determine total number of facade elements per building and assign number to building data type.
    843850    DO  nb = 1, num_build
    844851!
    845 !--    Allocate dummy array used for summing-up facade elements. 
    846 !--    Please note, dummy arguments are necessary as building-date type
    847 !--    arrays are not necessarily allocated on all PEs.
     852!--    Allocate dummy array used for summing-up facade elements.
     853!--    Please note, dummy arguments are necessary as building-date type arrays are not necessarily
     854!--    allocated on all PEs.
    848855       ALLOCATE( num_facades_h(buildings(nb)%kb_min:buildings(nb)%kb_max) )
    849856       ALLOCATE( num_facades_v(buildings(nb)%kb_min:buildings(nb)%kb_max) )
     
    860867       ENDIF
    861868
    862 #if defined( __parallel ) 
    863        CALL MPI_ALLREDUCE( num_facades_h,                                      &
    864                            receive_dum_h,                                      &
    865                            buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
    866                            MPI_INTEGER,                                        &
    867                            MPI_SUM,                                            &
    868                            comm2d,                                             &
     869#if defined( __parallel )
     870       CALL MPI_ALLREDUCE( num_facades_h,                                                          &
     871                           receive_dum_h,                                                          &
     872                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
     873                           MPI_INTEGER,                                                            &
     874                           MPI_SUM,                                                                &
     875                           comm2d,                                                                 &
    869876                           ierr )
    870877
    871        CALL MPI_ALLREDUCE( num_facades_v,                                      &
    872                            receive_dum_v,                                      &
    873                            buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
    874                            MPI_INTEGER,                                        &
    875                            MPI_SUM,                                            &
    876                            comm2d,                                             &
     878       CALL MPI_ALLREDUCE( num_facades_v,                                                          &
     879                           receive_dum_v,                                                          &
     880                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
     881                           MPI_INTEGER,                                                            &
     882                           MPI_SUM,                                                                &
     883                           comm2d,                                                                 &
    877884                           ierr )
    878        IF ( ALLOCATED( buildings(nb)%num_facade_h ) )                          &
    879            buildings(nb)%num_facade_h = receive_dum_h
    880        IF ( ALLOCATED( buildings(nb)%num_facade_v ) )                          &
    881            buildings(nb)%num_facade_v = receive_dum_v
     885       IF ( ALLOCATED( buildings(nb)%num_facade_h ) )  buildings(nb)%num_facade_h = receive_dum_h
     886       IF ( ALLOCATED( buildings(nb)%num_facade_v ) )  buildings(nb)%num_facade_v = receive_dum_v
    882887#else
    883888       buildings(nb)%num_facade_h = num_facades_h
     
    893898!
    894899!--    Allocate index arrays which link facade elements with surface-data type.
    895 !--    Please note, no height levels are considered here (information is stored
    896 !--    in surface-data type itself).
     900!--    Please note, no height levels are considered here (information is stored in surface-data type
     901!--    itself).
    897902       IF ( buildings(nb)%on_pe )  THEN
    898903!
     
    901906          buildings(nb)%num_facades_per_building_v = SUM( buildings(nb)%num_facade_v )
    902907!
    903 !--       Allocate arrays which link the building with the horizontal and vertical
    904 !--       urban-type surfaces. Please note, linking arrays are allocated over all
    905 !--       facade elements, which is required in case a building is located at the
    906 !--       subdomain boundaries, where the building and the corresponding surface
    907 !--       elements are located on different subdomains.
     908!--       Allocate arrays which link the building with the horizontal and vertical urban-type
     909!--       surfaces. Please note, linking arrays are allocated over all facade elements, which is
     910!--       required in case a building is located at the subdomain boundaries, where the building and
     911!--       the corresponding surface elements are located on different subdomains.
    908912          ALLOCATE( buildings(nb)%m_h(1:buildings(nb)%num_facades_per_building_h_l) )
    909913
     
    916920          buildings(nb)%vpf = 0.0_wp
    917921
    918           facade_area_v = 0.0_wp         
     922          facade_area_v = 0.0_wp
    919923          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    920              facade_area_v = facade_area_v + buildings(nb)%num_facade_v(k)     &
    921                              * dzw(k+1) * dx
     924             facade_area_v = facade_area_v + buildings(nb)%num_facade_v(k) * dzw(k+1) * dx
    922925          ENDDO
    923926!
    924 !--       Determine volume per total facade area (vpf). For the horizontal facade
    925 !--       area num_facades_per_building_h can be taken, multiplied with dx*dy.
    926 !--       However, due to grid stretching, vertical facade elements must be
    927 !--       summed-up vertically. Please note, if dx /= dy, an error is made!
    928           buildings(nb)%vpf = buildings(nb)%vol_tot /                          &
    929                         ( buildings(nb)%num_facades_per_building_h * dx * dy + &
    930                           facade_area_v )
     927!--       Determine volume per total facade area (vpf). For the horizontal facade area
     928!--       num_facades_per_building_h can be taken, multiplied with dx*dy.
     929!--       However, due to grid stretching, vertical facade elements must be summed-up vertically.
     930!--       Please note, if dx /= dy, an error is made!
     931          buildings(nb)%vpf = buildings(nb)%vol_tot /                                              &
     932                              ( buildings(nb)%num_facades_per_building_h * dx * dy + facade_area_v )
    931933!
    932934!--       Determine floor-area-per-facade.
    933           buildings(nb)%fapf = buildings(nb)%num_facades_per_building_h        &
    934                              * dx * dy                                         &
    935                              / ( buildings(nb)%num_facades_per_building_h      &
    936                                * dx * dy + facade_area_v )
     935          buildings(nb)%fapf = buildings(nb)%num_facades_per_building_h     * dx * dy              &
     936                               / ( buildings(nb)%num_facades_per_building_h * dx * dy              &
     937                                   + facade_area_v )
    937938       ENDIF
    938939    ENDDO
    939940!
    940 !-- Link facade elements with surface data type. 
     941!-- Link facade elements with surface data type.
    941942!-- Allocate array for counting.
    942943    ALLOCATE( n_fa(1:num_build) )
     
    947948       j = surf_usm_h%j(m) + surf_usm_h%joff
    948949
    949        nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
     950       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    950951
    951952       IF ( buildings(nb)%on_pe )  THEN
    952953          buildings(nb)%m_h(n_fa(nb)) = m
    953           n_fa(nb) = n_fa(nb) + 1 
     954          n_fa(nb) = n_fa(nb) + 1
    954955       ENDIF
    955956    ENDDO
     
    961962          j = surf_usm_v(l)%j(m) + surf_usm_v(l)%joff
    962963
    963           nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM = 1 )
     964          nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    964965
    965966          IF ( buildings(nb)%on_pe )  THEN
    966967             buildings(nb)%l_v(n_fa(nb)) = l
    967968             buildings(nb)%m_v(n_fa(nb)) = m
    968              n_fa(nb) = n_fa(nb) + 1   
     969             n_fa(nb) = n_fa(nb) + 1
    969970          ENDIF
    970971       ENDDO
     
    972973    DEALLOCATE( n_fa )
    973974!
    974 !-- Initialize building parameters, first by mean building type. Note,
    975 !-- in this case all buildings have the same type.
    976 !-- In a second step initialize with building tpyes from static input file,
    977 !-- where building types can be individual for each building.
     975!-- Initialize building parameters, first by mean building type. Note, in this case all buildings
     976!-- have the same type.
     977!-- In a second step initialize with building tpyes from static input file, where building types can
     978!-- be individual for each building.
    978979    buildings(:)%lambda_layer3       = building_pars(31,building_type)
    979980    buildings(:)%s_layer3            = building_pars(44,building_type)
    980981    buildings(:)%f_c_win             = building_pars(119,building_type)
    981     buildings(:)%g_value_win         = building_pars(120,building_type)   
    982     buildings(:)%u_value_win         = building_pars(121,building_type)       
    983     buildings(:)%eta_ve              = building_pars(124,building_type)   
    984     buildings(:)%factor_a            = building_pars(125,building_type)   
     982    buildings(:)%g_value_win         = building_pars(120,building_type)
     983    buildings(:)%u_value_win         = building_pars(121,building_type)
     984    buildings(:)%eta_ve              = building_pars(124,building_type)
     985    buildings(:)%factor_a            = building_pars(125,building_type)
    985986    buildings(:)%factor_c            = building_pars(126,building_type)
    986     buildings(:)%lambda_at           = building_pars(127,building_type)   
    987     buildings(:)%theta_int_h_set     = building_pars(13,building_type)   
     987    buildings(:)%lambda_at           = building_pars(127,building_type)
     988    buildings(:)%theta_int_h_set     = building_pars(13,building_type)
    988989    buildings(:)%theta_int_c_set     = building_pars(12,building_type)
    989     buildings(:)%q_h_max             = building_pars(128,building_type)   
    990     buildings(:)%q_c_max             = building_pars(129,building_type)         
     990    buildings(:)%q_h_max             = building_pars(128,building_type)
     991    buildings(:)%q_c_max             = building_pars(129,building_type)
    991992    buildings(:)%qint_high           = building_pars(130,building_type)
    992993    buildings(:)%qint_low            = building_pars(131,building_type)
     
    997998!
    998999!-- Initialize seasonal dependent parameters, depending on day of the year.
    999 !-- First, calculated day of the year. 
     1000!-- First, calculated day of the year.
    10001001    CALL get_date_time( time_since_reference_point, day_of_year = day_of_year )
    10011002!
    1002 !-- Summer is defined in between northward- and southward equinox.
    1003     IF ( day_of_year >= northward_equinox  .AND.                               &
    1004          day_of_year <= southward_equinox )  THEN
    1005        buildings(:)%air_change_low      = summer_pars(0,building_type)   
     1003!-- Summer is defined in between northward- and southward equinox.
     1004    IF ( day_of_year >= northward_equinox  .AND.  day_of_year <= southward_equinox )  THEN
     1005       buildings(:)%air_change_low      = summer_pars(0,building_type)
    10061006       buildings(:)%air_change_high     = summer_pars(1,building_type)
    10071007    ELSE
    1008        buildings(:)%air_change_low      = winter_pars(0,building_type)   
     1008       buildings(:)%air_change_low      = winter_pars(0,building_type)
    10091009       buildings(:)%air_change_high     = winter_pars(1,building_type)
    10101010    ENDIF
    10111011!
    1012 !-- Initialize ventilaation load. Please note, building types > 7 are actually
    1013 !-- not allowed (check already in urban_surface_mod and netcdf_data_input_mod.
    1014 !-- However, the building data base may be later extended. 
    1015     IF ( building_type ==  1  .OR.  building_type ==  2  .OR.                  &
    1016          building_type ==  3  .OR.  building_type == 10  .OR.                  &
     1012!-- Initialize ventilation load. Please note, building types > 7 are actually not allowed (check
     1013!-- already in urban_surface_mod and netcdf_data_input_mod.
     1014!-- However, the building data base may be later extended.
     1015    IF ( building_type ==  1  .OR.  building_type ==  2  .OR.                                      &
     1016         building_type ==  3  .OR.  building_type == 10  .OR.                                      &
    10171017         building_type == 11  .OR.  building_type == 12 )  THEN
    10181018       buildings(:)%ventilation_int_loads = 1
    10191019!
    10201020!-- Office, building with large windows
    1021     ELSEIF ( building_type ==  4  .OR.  building_type ==  5  .OR.              &
    1022              building_type ==  6  .OR.  building_type ==  7  .OR.              &
     1021    ELSEIF ( building_type ==  4  .OR.  building_type ==  5  .OR.                                  &
     1022             building_type ==  6  .OR.  building_type ==  7  .OR.                                  &
    10231023             building_type ==  8  .OR.  building_type ==  9)  THEN
    10241024       buildings(:)%ventilation_int_loads = 2
    10251025!
    10261026!-- Industry, hospitals
    1027     ELSEIF ( building_type == 13  .OR.  building_type == 14  .OR.              &
    1028              building_type == 15  .OR.  building_type == 16  .OR.              &
     1027    ELSEIF ( building_type == 13  .OR.  building_type == 14  .OR.                                  &
     1028             building_type == 15  .OR.  building_type == 16  .OR.                                  &
    10291029             building_type == 17  .OR.  building_type == 18 )  THEN
    10301030       buildings(:)%ventilation_int_loads = 3
     
    10361036          DO  j = nys, nyn
    10371037              IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    1038                  nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), &
    1039                               DIM = 1 )
     1038                 nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    10401039                 bt = building_type_f%var(j,i)
    1041                  
     1040
    10421041                 buildings(nb)%lambda_layer3       = building_pars(31,bt)
    10431042                 buildings(nb)%s_layer3            = building_pars(44,bt)
    10441043                 buildings(nb)%f_c_win             = building_pars(119,bt)
    1045                  buildings(nb)%g_value_win         = building_pars(120,bt)   
    1046                  buildings(nb)%u_value_win         = building_pars(121,bt)   
    1047                  buildings(nb)%eta_ve              = building_pars(124,bt)   
    1048                  buildings(nb)%factor_a            = building_pars(125,bt)   
     1044                 buildings(nb)%g_value_win         = building_pars(120,bt)
     1045                 buildings(nb)%u_value_win         = building_pars(121,bt)
     1046                 buildings(nb)%eta_ve              = building_pars(124,bt)
     1047                 buildings(nb)%factor_a            = building_pars(125,bt)
    10491048                 buildings(nb)%factor_c            = building_pars(126,bt)
    1050                  buildings(nb)%lambda_at           = building_pars(127,bt)   
    1051                  buildings(nb)%theta_int_h_set     = building_pars(13,bt)   
     1049                 buildings(nb)%lambda_at           = building_pars(127,bt)
     1050                 buildings(nb)%theta_int_h_set     = building_pars(13,bt)
    10521051                 buildings(nb)%theta_int_c_set     = building_pars(12,bt)
    1053                  buildings(nb)%q_h_max             = building_pars(128,bt)   
    1054                  buildings(nb)%q_c_max             = building_pars(129,bt)         
     1052                 buildings(nb)%q_h_max             = building_pars(128,bt)
     1053                 buildings(nb)%q_c_max             = building_pars(129,bt)
    10551054                 buildings(nb)%qint_high           = building_pars(130,bt)
    10561055                 buildings(nb)%qint_low            = building_pars(131,bt)
    10571056                 buildings(nb)%height_storey       = building_pars(132,bt)
    1058                  buildings(nb)%height_cei_con      = building_pars(133,bt) 
     1057                 buildings(nb)%height_cei_con      = building_pars(133,bt)
    10591058                 buildings(nb)%params_waste_heat_h = building_pars(134,bt)
    10601059                 buildings(nb)%params_waste_heat_c = building_pars(135,bt)
    10611060
    1062               IF ( day_of_year >= northward_equinox  .AND.                     &
    1063                    day_of_year <= southward_equinox )  THEN
    1064                  buildings(nb)%air_change_low      = summer_pars(0,bt)   
     1061              IF ( day_of_year >= northward_equinox  .AND.  day_of_year <= southward_equinox )  THEN
     1062                 buildings(nb)%air_change_low      = summer_pars(0,bt)
    10651063                 buildings(nb)%air_change_high     = summer_pars(1,bt)
    10661064              ELSE
    1067                  buildings(nb)%air_change_low      = winter_pars(0,bt)   
     1065                 buildings(nb)%air_change_low      = winter_pars(0,bt)
    10681066                 buildings(nb)%air_change_high     = winter_pars(1,bt)
    10691067              ENDIF
    10701068
    10711069!
    1072 !--              Initialize ventilaation load. Please note, building types > 7 
    1073 !--              are actually not allowed (check already in urban_surface_mod 
    1074 !--              and netcdf_data_input_mod. However, the building data base may 
    1075 !--              be later extended. 
    1076                  IF ( bt ==  1  .OR.  bt ==  2  .OR.                           &
    1077                       bt ==  3  .OR.  bt == 10  .OR.                           &
     1070!--              Initialize ventilaation load. Please note, building types > 7
     1071!--              are actually not allowed (check already in urban_surface_mod
     1072!--              and netcdf_data_input_mod. However, the building data base may
     1073!--              be later extended.
     1074                 IF ( bt ==  1  .OR.  bt ==  2  .OR.                                               &
     1075                      bt ==  3  .OR.  bt == 10  .OR.                                               &
    10781076                      bt == 11  .OR.  bt == 12 )  THEN
    10791077                    buildings(nb)%ventilation_int_loads = 1
    1080 !                   
     1078!
    10811079!--              Office, building with large windows
    1082                  ELSEIF ( bt ==  4  .OR.  bt ==  5  .OR.                       &
    1083                           bt ==  6  .OR.  bt ==  7  .OR.                       &
     1080                 ELSEIF ( bt ==  4  .OR.  bt ==  5  .OR.                                           &
     1081                          bt ==  6  .OR.  bt ==  7  .OR.                                           &
    10841082                          bt ==  8  .OR.  bt ==  9)  THEN
    10851083                    buildings(nb)%ventilation_int_loads = 2
    10861084!
    10871085!--              Industry, hospitals
    1088                  ELSEIF ( bt == 13  .OR.  bt == 14  .OR.                       &
    1089                           bt == 15  .OR.  bt == 16  .OR.                       &
     1086                 ELSEIF ( bt == 13  .OR.  bt == 14  .OR.                                           &
     1087                          bt == 15  .OR.  bt == 16  .OR.                                           &
    10901088                          bt == 17  .OR.  bt == 18 )  THEN
    10911089                    buildings(nb)%ventilation_int_loads = 3
     
    10961094    ENDIF
    10971095!
    1098 !-- Calculation of surface-related heat transfer coeffiecient
    1099 !-- out of standard u-values from building database
    1100 !-- only amount of extern and surface is used
    1101 !-- otherwise amount between air and surface taken account twice
     1096!-- Calculation of surface-related heat transfer coeffiecient out of standard u-values from building
     1097!-- database.
     1098!-- Only amount of extern and surface is used.
     1099!-- Otherwise amount between air and surface taken account twice.
    11021100    DO nb = 1, num_build
    1103        IF ( buildings(nb)%on_pe ) THEN   
     1101       IF ( buildings(nb)%on_pe ) THEN
    11041102          du_win_tmp = 1.0_wp / buildings(nb)%u_value_win
    1105           u_tmp = buildings(nb)%u_value_win * ( du_win_tmp / ( du_win_tmp -    &
     1103          u_tmp = buildings(nb)%u_value_win * ( du_win_tmp / ( du_win_tmp -                        &
    11061104                  0.125_wp + ( 1.0_wp / h_is ) ) )
    1107                  
     1105
    11081106          du_tmp = 1.0_wp / u_tmp
    1109          
     1107
    11101108          buildings(nb)%h_es = 1.0_wp / ( du_tmp - ( 1.0_wp / h_is ) )
    11111109
     
    11191117!-- Initialize indoor temperature. Actually only for output at initial state.
    11201118    DO  nb = 1, num_build
    1121        IF ( buildings(nb)%on_pe )                                              &
    1122           buildings(nb)%t_in(:) = initial_indoor_temperature
     1119       IF ( buildings(nb)%on_pe )  buildings(nb)%t_in(:) = initial_indoor_temperature
    11231120    ENDDO
    11241121
     
    11281125
    11291126
    1130 !------------------------------------------------------------------------------!
     1127!--------------------------------------------------------------------------------------------------!
    11311128! Description:
    11321129! ------------
    11331130!> Main part of the indoor model.
    11341131!> Calculation of .... (kanani: Please describe)
    1135 !------------------------------------------------------------------------------!
     1132!--------------------------------------------------------------------------------------------------!
    11361133 SUBROUTINE im_main_heatcool
    11371134
     
    11391136!         ONLY:  c_p
    11401137
    1141     USE control_parameters,                                                    &
     1138    USE control_parameters,                                                                        &
    11421139        ONLY:  time_since_reference_point
    11431140
    1144     USE grid_variables,                                                        &
     1141    USE grid_variables,                                                                            &
    11451142        ONLY:  dx, dy
    11461143
    11471144    USE pegrid
    1148    
    1149     USE surface_mod,                                                           &
     1145
     1146    USE surface_mod,                                                                               &
    11501147        ONLY:  ind_veg_wall, ind_wat_win, surf_usm_h, surf_usm_v
    11511148
    1152     USE urban_surface_mod,                                                     &
    1153         ONLY:  nzt_wall, t_wall_h, t_wall_v, t_window_h, t_window_v,           &
    1154                building_type
    1155 
     1149    USE urban_surface_mod,                                                                         &
     1150        ONLY:  building_type, nzt_wall, t_wall_h, t_wall_v, t_window_h, t_window_v
     1151
     1152
     1153    INTEGER(iwp) ::  fa   !< running index for facade elements of each building
    11561154    INTEGER(iwp) ::  i    !< index of facade-adjacent atmosphere grid point in x-direction
    11571155    INTEGER(iwp) ::  j    !< index of facade-adjacent atmosphere grid point in y-direction
     
    11611159    INTEGER(iwp) ::  m    !< running index surface elements
    11621160    INTEGER(iwp) ::  nb   !< running index for buildings
    1163     INTEGER(iwp) ::  fa   !< running index for facade elements of each building
    11641161
    11651162    REAL(wp) ::  indoor_wall_window_temperature   !< weighted temperature of innermost wall/window layer
     
    11711168    REAL(wp), DIMENSION(:), ALLOCATABLE ::  t_in_recv     !< dummy recv buffer used for summing-up indoor temperature per kk-level
    11721169!
    1173 !-- Determine time of day in hours. 
     1170!-- Determine time of day in hours.
    11741171    CALL get_date_time( time_since_reference_point, second_of_day=second_of_day )
    11751172    time_utc_hour = second_of_day / seconds_per_hour
     
    11781175    DO  nb = 1, num_build
    11791176!
    1180 !--    First, check whether building is present on local subdomain. 
     1177!--    First, check whether building is present on local subdomain.
    11811178       IF ( buildings(nb)%on_pe )  THEN
    11821179!
    11831180!--       Determine daily schedule. 08:00-18:00 = 1, other hours = 0.
    1184 !--       Residental Building, panel WBS 70   
     1181!--       Residental Building, panel WBS 70
    11851182          IF ( buildings(nb)%ventilation_int_loads == 1 )  THEN
    11861183             IF ( time_utc_hour >= 8.0_wp  .AND.  time_utc_hour <= 18.0_wp )  THEN
     
    11991196             ENDIF
    12001197          ENDIF
    1201 !       
     1198!
    12021199!--       Industry, hospitals
    12031200          IF ( buildings(nb)%ventilation_int_loads == 3 )  THEN
     
    12101207!
    12111208!--       Initialize/reset indoor temperature
    1212           buildings(nb)%t_in_l = 0.0_wp 
     1209          buildings(nb)%t_in_l = 0.0_wp
    12131210!
    12141211!--       Horizontal surfaces
    12151212          DO  fa = 1, buildings(nb)%num_facades_per_building_h_l
    12161213!
    1217 !--          Determine index where corresponding surface-type information
    1218 !--          is stored.
     1214!--          Determine index where corresponding surface-type information is stored.
    12191215             m = buildings(nb)%m_h(fa)
    12201216!
    1221 !--          Determine building height level index. 
     1217!--          Determine building height level index.
    12221218             kk = surf_usm_h%k(m) + surf_usm_h%koff
    12231219!
    12241220!--          Building geometries --> not time-dependent
    1225              facade_element_area          = dx * dy                               !< [m2] surface area per facade element   
     1221             facade_element_area          = dx * dy                               !< [m2] surface area per facade element
    12261222             floor_area_per_facade        = buildings(nb)%fapf                    !< [m2/m2] floor area per facade area
    1227              indoor_volume_per_facade     = buildings(nb)%vpf(kk)                 !< [m3/m2] indoor air volume per facade area
    1228              buildings(nb)%area_facade    = facade_element_area *                                   &
    1229                                           ( buildings(nb)%num_facades_per_building_h +              &
    1230                                             buildings(nb)%num_facades_per_building_v )                !< [m2] area of total facade
    1231              window_area_per_facade       = surf_usm_h%frac(m,ind_wat_win)  * facade_element_area     !< [m2] window area per facade element
     1223             indoor_volume_per_facade     = buildings(nb)%vpf(kk)                 !< [m3/m2] indoor air volume per facade area
     1224             buildings(nb)%area_facade    = facade_element_area *                                  &
     1225                                            ( buildings(nb)%num_facades_per_building_h +           &
     1226                                              buildings(nb)%num_facades_per_building_v )              !< [m2] area of total facade
     1227             window_area_per_facade       = surf_usm_h%frac(m,ind_wat_win)  * facade_element_area     !< [m2] window area per facade
     1228                                                                                                      !< element
    12321229
    12331230             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
    1234              total_area                   = buildings(nb)%net_floor_area                              !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
    1235              a_m                          = buildings(nb)%factor_a * total_area *                   &
    1236                                           ( facade_element_area / buildings(nb)%area_facade ) *     &
    1237                                             buildings(nb)%lambda_at                                   !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
    1238              c_m                          = buildings(nb)%factor_c * total_area *                   &
    1239                                           ( facade_element_area / buildings(nb)%area_facade )         !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)             
     1231             total_area                   = buildings(nb)%net_floor_area                            !< [m2] area of all surfaces
     1232                                                                                                    !< pointing to zone  Eq. (9) according to section 7.2.2.2
     1233             a_m                          = buildings(nb)%factor_a * total_area *                  &
     1234                                            ( facade_element_area / buildings(nb)%area_facade ) *  &
     1235                                            buildings(nb)%lambda_at                                 !< [m2] standard values
     1236                                                                                                    !< according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
     1237             c_m                          = buildings(nb)%factor_c * total_area *                  &
     1238                                            ( facade_element_area / buildings(nb)%area_facade )     !< [J/K] standard values
     1239                                                                                                    !< according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
    12401240!
    12411241!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
    12421242             h_t_es   = window_area_per_facade * buildings(nb)%h_es                                   !< [W/K] only for windows
    12431243
    1244              h_t_is  = buildings(nb)%area_facade  * h_is                                                             !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
    1245              h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
    1246              h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )     & !< [W/K]
     1244             h_t_is  = buildings(nb)%area_facade * h_is                                               !< [W/K] with h_is = 3.45 W /
     1245                                                                                                      !< (m2 K) between surface and air, Eq. (9)
     1246             h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W /
     1247                                                                                                      !< (m2 K) between component and surface, Eq. (64)
     1248             h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )    &  !< [W/K]
    12471249                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp &
    12481250                                             ) + 1.0_wp / h_t_ms )                                    !< [W/K] opaque components
    1249              h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63), Section 12.2.2
    1250 !
    1251 !--          internal air loads dependent on the occupacy of the room
    1252 !--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
    1253              phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low )  &
    1254                               * floor_area_per_facade )
     1251             h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63),
     1252                                                                                                      !< Section 12.2.2
     1253!
     1254!--          Internal air loads dependent on the occupacy of the room.
     1255!--          Basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int).
     1256             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low ) &
     1257                              * floor_area_per_facade )
    12551258             q_int = phi_ia / total_area
    12561259!
    1257 !--          Airflow dependent on the occupacy of the room
    1258 !--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
    1259              air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low )  !< [1/h]? 
    1260 !
    1261 !--          Heat transfer of ventilation 
    1262 !--          not less than 0.01 W/K to provide division by 0 in further calculations
    1263 !--          with heat capacity of air 0.33 Wh/m2K
    1264              h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *      &
    1265                                     0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
     1260!--          Airflow dependent on the occupacy of the room.
     1261!--          Basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
     1262             air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low )  !< [1/h]?
     1263!
     1264!--          Heat transfer of ventilation.
     1265!--          Not less than 0.01 W/K to avoid division by 0 in further calculations with heat
     1266!--          capacity of air 0.33 Wh/m2K.
     1267             h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                      &
     1268                                      0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )    !< [W/K] from ISO 13789 Eq.(10)
    12661269
    12671270!--          Heat transfer coefficient auxiliary variables
     
    12781281             k = surf_usm_h%k(m)
    12791282             near_facade_temperature = surf_usm_h%pt_10cm(m)
    1280              indoor_wall_window_temperature =                                  &
    1281                   surf_usm_h%frac(m,ind_veg_wall) * t_wall_h(nzt_wall,m)       &
    1282                 + surf_usm_h%frac(m,ind_wat_win)  * t_window_h(nzt_wall,m)
    1283 !
    1284 !--          Solar thermal gains. If net_sw_in larger than sun-protection
    1285 !--          threshold parameter (params_solar_protection), sun protection will
    1286 !--          be activated
    1287              IF ( net_sw_in <= params_solar_protection )  THEN
     1283             indoor_wall_window_temperature =                                                      &
     1284                                            surf_usm_h%frac(m,ind_veg_wall) * t_wall_h(nzt_wall,m) &
     1285                                          + surf_usm_h%frac(m,ind_wat_win)  * t_window_h(nzt_wall,m)
     1286!
     1287!--          Solar thermal gains. If net_sw_in larger than sun-protection threshold parameter
     1288!--          (params_solar_protection), sun protection will be activated.
     1289             IF ( net_sw_in <= params_solar_protection )  THEN
    12881290                solar_protection_off = 1
    12891291                solar_protection_on  = 0
    1290              ELSE 
     1292             ELSE
    12911293                solar_protection_off = 0
    12921294                solar_protection_on  = 1
    12931295             ENDIF
    12941296!
    1295 !--          Calculation of total heat gains from net_sw_in through windows [W] in respect on automatic sun protection
     1297!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on
     1298!--          automatic sun protection.
    12961299!--          DIN 4108 - 2 chap.8
    1297              phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off                           &
    1298                          + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win * solar_protection_on )  &
     1300             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
     1301                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win *            &
     1302                           solar_protection_on )                                                   &
    12991303                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w
    1300              q_sol = phi_sol           
    1301 !
    1302 !--          Calculation of the mass specific thermal load for internal and external heatsources of the inner node
    1303              phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )                                    !< [W] Eq. (C.2) with phi_ia=0,5*phi_int
     1304             q_sol = phi_sol
     1305!
     1306!--          Calculation of the mass specific thermal load for internal and external heatsources of
     1307!--          the inner node.
     1308             phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )                                    !< [W] Eq. (C.2) with
     1309                                                                                                    !< phi_ia=0,5*phi_int
    13041310             q_c_m = phi_m
    13051311!
    1306 !--          Calculation mass specific thermal load implied non thermal mass
    1307              phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) ) &
    1308                        * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
    1309              q_c_st = phi_st           
     1312!--          Calculation mass specific thermal load implied non thermal mass
     1313             phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )  &
     1314                       * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with
     1315                                                                                                    !< phi_ia=0,5*phi_int
     1316             q_c_st = phi_st
    13101317!
    13111318!--          Calculations for deriving indoor temperature and heat flux into the wall
    1312 !--          Step 1: Indoor temperature without heating and cooling
     1319!--          Step 1: indoor temperature without heating and cooling
    13131320!--          section C.4.1 Picture C.2 zone 3)
    13141321             phi_hc_nd = 0.0_wp
    1315              
    1316              CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1317                                          near_facade_temperature, phi_hc_nd )
    1318 !
    1319 !--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready   
    1320              IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.  theta_air <= buildings(nb)%theta_int_c_set )  THEN
     1322
     1323             CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                 &
     1324                                          near_facade_temperature, phi_hc_nd )
     1325!
     1326!--          If air temperature between border temperatures of heating and cooling, assign output
     1327!--          variable, then ready.
     1328             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.                                &
     1329                  theta_air <= buildings(nb)%theta_int_c_set )  THEN
    13211330                phi_hc_nd_ac = 0.0_wp
    1322                 phi_hc_nd    = phi_hc_nd_ac           
     1331                phi_hc_nd    = phi_hc_nd_ac
    13231332                theta_air_ac = theta_air
    13241333!
     
    13281337!
    13291338!--             Temperature not correct, calculation method according to section C4.2
    1330                 theta_air_0 = theta_air                                                  !< temperature without heating/cooling 
     1339                theta_air_0 = theta_air                                                  !< temperature without heating/cooling
    13311340!
    13321341!--             Heating or cooling?
    13331342                IF ( theta_air_0 > buildings(nb)%theta_int_c_set )  THEN
    13341343                   theta_air_set = buildings(nb)%theta_int_c_set
    1335                 ELSE 
    1336                    theta_air_set = buildings(nb)%theta_int_h_set 
     1344                ELSE
     1345                   theta_air_set = buildings(nb)%theta_int_h_set
    13371346                ENDIF
    13381347!
    1339 !--             Calculate the temperature with phi_hc_nd_10 
     1348!--             Calculate the temperature with phi_hc_nd_10
    13401349                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
    13411350                phi_hc_nd    = phi_hc_nd_10
    1342                
    1343                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1344                                             near_facade_temperature, phi_hc_nd )
     1351
     1352                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
     1353                                             near_facade_temperature, phi_hc_nd )
    13451354                theta_air_10 = theta_air                                                !< temperature with 10 W/m2 of heating
    1346                 phi_hc_nd_un = phi_hc_nd_10 * (theta_air_set - theta_air_0)          &
     1355                phi_hc_nd_un = phi_hc_nd_10 * (theta_air_set - theta_air_0)                        &
    13471356                                            / (theta_air_10  - theta_air_0)             !< Eq. (C.13)
    13481357!
    1349 !--             Step 3: With temperature ratio to determine the heating or cooling capacity   
    1350 !--             If necessary, limit the power to maximum power
     1358!--             Step 3: with temperature ratio to determine the heating or cooling capacity.
     1359!--             If necessary, limit the power to maximum power.
    13511360!--             section C.4.1 Picture C.2 zone 2) and 4)
    1352                 buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade             
     1361                buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade
    13531362                buildings(nb)%phi_h_max = buildings(nb)%q_h_max * floor_area_per_facade
    1354                 IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
     1363                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.                                 &
     1364                     phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
    13551365                   phi_hc_nd_ac = phi_hc_nd_un
    1356                    phi_hc_nd = phi_hc_nd_un 
     1366                   phi_hc_nd = phi_hc_nd_un
    13571367                ELSE
    13581368!
    1359 !--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
     1369!--             Step 4: inner temperature with maximum heating (phi_hc_nd_un positive) or cooling
     1370!--                     (phi_hc_nd_un negative)
    13601371!--             section C.4.1 Picture C.2 zone 1) and 5)
    13611372                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
    13621373                      phi_hc_nd_ac = buildings(nb)%phi_h_max                            !< Limit heating
    1363                    ELSE 
     1374                   ELSE
    13641375                      phi_hc_nd_ac = buildings(nb)%phi_c_max                            !< Limit cooling
    13651376                   ENDIF
    13661377                ENDIF
    1367                 phi_hc_nd = phi_hc_nd_ac   
     1378                phi_hc_nd = phi_hc_nd_ac
    13681379!
    13691380!--             Calculate the temperature with phi_hc_nd_ac (new)
    1370                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1371                                             near_facade_temperature, phi_hc_nd )
     1381                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
     1382                                             near_facade_temperature, phi_hc_nd )
    13721383                theta_air_ac = theta_air
    13731384             ENDIF
     
    13751386!--          Update theta_m_t_prev
    13761387             theta_m_t_prev = theta_m_t
    1377              
     1388
    13781389             q_vent = h_v * ( theta_air - near_facade_temperature )
    13791390!
    1380 !--          Calculate the operating temperature with weighted mean temperature of air and mean solar temperature
    1381 !--          Will be used for thermal comfort calculations
     1391!--          Calculate the operating temperature with weighted mean temperature of air and mean
     1392!--          solar temperature.
     1393!--          Will be used for thermal comfort calculations.
    13821394             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s          !< [degree_C] operative Temperature Eq. (C.12)
    13831395!              surf_usm_h%t_indoor(m) = theta_op                               !< not integrated now
    13841396!
    1385 !--          Heat flux into the wall. Value needed in urban_surface_mod to 
     1397!--          Heat flux into the wall. Value needed in urban_surface_mod to
    13861398!--          calculate heat transfer through wall layers towards the facade
    13871399!--          (use c_p * rho_surface to convert [W/m2] into [K m/s])
    1388              q_wall_win = h_t_ms * ( theta_s - theta_m )                       &
    1389                                     / (   facade_element_area                  &
    1390                                         - window_area_per_facade )
    1391              q_trans = q_wall_win * facade_element_area                                       
     1400             q_wall_win = h_t_ms * ( theta_s - theta_m )                                           &
     1401                                    / ( facade_element_area - window_area_per_facade )
     1402             q_trans = q_wall_win * facade_element_area
    13921403!
    13931404!--          Transfer q_wall_win back to USM (innermost wall/window layer)
     
    13951406             surf_usm_h%iwghf_eb_window(m) = q_wall_win
    13961407!
    1397 !--          Sum up operational indoor temperature per kk-level. Further below,
    1398 !--          this temperature is reduced by MPI to one temperature per kk-level
    1399 !--          and building (processor overlapping)
     1408!--          Sum up operational indoor temperature per kk-level. Further below, this temperature is
     1409!--          reduced by MPI to one temperature per kk-level and building (processor overlapping).
    14001410             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
    14011411!
    1402 !--          Calculation of waste heat
    1403 !--          Anthropogenic heat output
    1404              IF ( phi_hc_nd_ac > 0.0_wp )  THEN 
     1412!--          Calculation of waste heat.
     1413!--          Anthropogenic heat output.
     1414             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
    14051415                heating_on = 1
    14061416                cooling_on = 0
    1407              ELSE 
     1417             ELSE
    14081418                heating_on = 0
    14091419                cooling_on = -1
    14101420             ENDIF
    14111421
    1412              q_waste_heat = ( phi_hc_nd * (                                    &
    1413                               buildings(nb)%params_waste_heat_h * heating_on + &
    1414                               buildings(nb)%params_waste_heat_c * cooling_on ) &
    1415                             ) / facade_element_area                                               !< [W/m2] , observe the directional convention in PALM!
     1422             q_waste_heat = ( phi_hc_nd * (                                                        &
     1423                              buildings(nb)%params_waste_heat_h * heating_on +                     &
     1424                              buildings(nb)%params_waste_heat_c * cooling_on )                     &
     1425                            ) / facade_element_area                                             !< [W/m2] , observe the directional
     1426                                                                                                !< convention in PALM!
    14161427             surf_usm_h%waste_heat(m) = q_waste_heat
    14171428          ENDDO !< Horizontal surfaces loop
     
    14201431          DO  fa = 1, buildings(nb)%num_facades_per_building_v_l
    14211432!
    1422 !--          Determine indices where corresponding surface-type information
    1423 !--          is stored.
     1433!--          Determine indices where corresponding surface-type information is stored.
    14241434             l = buildings(nb)%l_v(fa)
    14251435             m = buildings(nb)%m_v(fa)
    14261436!
    1427 !--          Determine building height level index. 
     1437!--          Determine building height level index.
    14281438             kk = surf_usm_v(l)%k(m) + surf_usm_v(l)%koff
    14291439!
    1430 !--          (SOME OF THE FOLLOWING (not time-dependent COULD PROBABLY GO INTO A FUNCTION
     1440!--          (SOME OF THE FOLLOWING (not time-dependent) COULD PROBABLY GO INTO A FUNCTION
    14311441!--          EXCEPT facade_element_area, EVERYTHING IS CALCULATED EQUALLY)
    14321442!--          Building geometries  --> not time-dependent
     
    14351445
    14361446             floor_area_per_facade        = buildings(nb)%fapf                  !< [m2/m2] floor area per facade area
    1437              indoor_volume_per_facade     = buildings(nb)%vpf(kk)               !< [m3/m2] indoor air volume per facade area
    1438              buildings(nb)%area_facade    = facade_element_area *                                   &
    1439                                           ( buildings(nb)%num_facades_per_building_h +              &
    1440                                             buildings(nb)%num_facades_per_building_v )                !< [m2] area of total facade
    1441              window_area_per_facade       = surf_usm_v(l)%frac(m,ind_wat_win)  * facade_element_area  !< [m2] window area per facade element
     1447             indoor_volume_per_facade     = buildings(nb)%vpf(kk)               !< [m3/m2] indoor air volume per facade area
     1448             buildings(nb)%area_facade    = facade_element_area *                                  &
     1449                                            ( buildings(nb)%num_facades_per_building_h +           &
     1450                                              buildings(nb)%num_facades_per_building_v )              !< [m2] area of total facade
     1451             window_area_per_facade       = surf_usm_v(l)%frac(m,ind_wat_win) * facade_element_area   !< [m2] window area per
     1452                                                                                                      !< facade element
    14421453
    14431454             buildings(nb)%net_floor_area = buildings(nb)%vol_tot / ( buildings(nb)%height_storey )
    1444              total_area                   = buildings(nb)%net_floor_area                              !< [m2] area of all surfaces pointing to zone  Eq. (9) according to section 7.2.2.2
    1445              a_m                          = buildings(nb)%factor_a * total_area *                   &
    1446                                           ( facade_element_area / buildings(nb)%area_facade ) *     &
    1447                                             buildings(nb)%lambda_at                                   !< [m2] standard values according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
     1455             total_area                   = buildings(nb)%net_floor_area                              !< [m2] area of all surfaces
     1456                                                                                                      !< pointing to zone  Eq. (9) according to section 7.2.2.2
     1457             a_m                          = buildings(nb)%factor_a * total_area *                  &
     1458                                            ( facade_element_area / buildings(nb)%area_facade ) *  &
     1459                                              buildings(nb)%lambda_at                                 !< [m2] standard values
     1460                                                                                                      !< according to Table 12 section 12.3.1.2  (calculate over Eq. (65) according to section 12.3.1.2)
    14481461             c_m                          = buildings(nb)%factor_c * total_area *                   &
    1449                                           ( facade_element_area / buildings(nb)%area_facade )         !< [J/K] standard values according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
     1462                                            ( facade_element_area / buildings(nb)%area_facade )       !< [J/K] standard values
     1463                                                                                                      !< according to table 12 section 12.3.1.2 (calculate over Eq. (66) according to section 12.3.1.2)
    14501464!
    14511465!--          Calculation of heat transfer coefficient for transmission --> not time-dependent
    14521466             h_t_es   = window_area_per_facade * buildings(nb)%h_es                                   !< [W/K] only for windows
    14531467
    1454              h_t_is  = buildings(nb)%area_facade  * h_is                                                             !< [W/K] with h_is = 3.45 W / (m2 K) between surface and air, Eq. (9)
    1455              h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W / (m2 K) between component and surface, Eq. (64)
    1456              h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )     & !< [W/K]
     1468             h_t_is  = buildings(nb)%area_facade  * h_is                                              !< [W/K] with h_is = 3.45 W /
     1469                                                                                                      !< (m2 K) between surface and air, Eq. (9)
     1470             h_t_ms  = a_m * h_ms                                                                     !< [W/K] with h_ms = 9.10 W /
     1471                                                                                                      !< (m2 K) between component and surface, Eq. (64)
     1472             h_t_wall  = 1.0_wp / ( 1.0_wp / ( ( facade_element_area - window_area_per_facade )    &  !< [W/K]
    14571473                                    * buildings(nb)%lambda_layer3 / buildings(nb)%s_layer3 * 0.5_wp &
    14581474                                             ) + 1.0_wp / h_t_ms )                                    !< [W/K] opaque components
    14591475             h_t_wm  = 1.0_wp / ( 1.0_wp / h_t_wall - 1.0_wp / h_t_ms )                               !< [W/K] emmision Eq. (63), Section 12.2.2
    14601476!
    1461 !--          internal air loads dependent on the occupacy of the room
    1462 !--          basical internal heat gains (qint_low) with additional internal heat gains by occupancy (qint_high) (0,5*phi_int)
    1463              phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low )  &
    1464                               * floor_area_per_facade )
     1477!--          Internal air loads dependent on the occupacy of the room.
     1478!--          Basical internal heat gains (qint_low) with additional internal heat gains by occupancy
     1479!--          (qint_high) (0,5*phi_int)
     1480             phi_ia = 0.5_wp * ( ( buildings(nb)%qint_high * schedule_d + buildings(nb)%qint_low ) &
     1481                             * floor_area_per_facade )
    14651482             q_int = phi_ia
    14661483
    14671484!
    1468 !--          Airflow dependent on the occupacy of the room
    1469 !--          basical airflow (air_change_low) with additional airflow gains by occupancy (air_change_high)
    1470              air_change = ( buildings(nb)%air_change_high * schedule_d + buildings(nb)%air_change_low ) 
    1471 !
    1472 !--          Heat transfer of ventilation
    1473 !--          not less than 0.01 W/K to provide division by 0 in further calculations
    1474 !--          with heat capacity of air 0.33 Wh/m2K
    1475              h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                       &
    1476                                     0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )                    !< [W/K] from ISO 13789 Eq.(10)
    1477                                    
     1485!--          Airflow dependent on the occupacy of the room.
     1486!--          Basical airflow (air_change_low) with additional airflow gains by occupancy
     1487!--          (air_change_high)
     1488             air_change = ( buildings(nb)%air_change_high * schedule_d +                           &
     1489                          buildings(nb)%air_change_low )
     1490!
     1491!--          Heat transfer of ventilation.
     1492!--          Not less than 0.01 W/K to avoid division by 0 in further calculations with heat
     1493!--          capacity of air 0.33 Wh/m2K
     1494             h_v   = MAX( 0.01_wp , ( air_change * indoor_volume_per_facade *                      &
     1495                                    0.33_wp * (1.0_wp - buildings(nb)%eta_ve ) ) )                    !< [W/K] from ISO 13789
     1496                                                                                                      !< Eq.(10)
     1497
    14781498!--          Heat transfer coefficient auxiliary variables
    14791499             h_t_1 = 1.0_wp / ( ( 1.0_wp / h_v )   + ( 1.0_wp / h_t_is ) )                            !< [W/K] Eq. (C.6)
     
    14861506!--          Quantities needed for im_calc_temperatures
    14871507             i = surf_usm_v(l)%i(m)
    1488              j = surf_usm_v(l)%j(m)   
     1508             j = surf_usm_v(l)%j(m)
    14891509             k = surf_usm_v(l)%k(m)
    14901510             near_facade_temperature = surf_usm_v(l)%pt_10cm(m)
    1491              indoor_wall_window_temperature =                                                       &
    1492                   surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%t(nzt_wall,m)                    &
    1493                 + surf_usm_v(l)%frac(m,ind_wat_win)  * t_window_v(l)%t(nzt_wall,m)
    1494 !
    1495 !--          Solar thermal gains. If net_sw_in larger than sun-protection 
    1496 !--          threshold parameter (params_solar_protection), sun protection will 
     1511             indoor_wall_window_temperature =                                                      &
     1512                                    surf_usm_v(l)%frac(m,ind_veg_wall) * t_wall_v(l)%t(nzt_wall,m) &
     1513                                  + surf_usm_v(l)%frac(m,ind_wat_win)  * t_window_v(l)%t(nzt_wall,m)
     1514!
     1515!--          Solar thermal gains. If net_sw_in larger than sun-protection
     1516!--          threshold parameter (params_solar_protection), sun protection will
    14971517!--          be activated
    1498              IF ( net_sw_in <= params_solar_protection )  THEN 
     1518             IF ( net_sw_in <= params_solar_protection )  THEN
    14991519                solar_protection_off = 1
    1500                 solar_protection_on  = 0 
    1501              ELSE 
     1520                solar_protection_on  = 0
     1521             ELSE
    15021522                solar_protection_off = 0
    1503                 solar_protection_on  = 1 
     1523                solar_protection_on  = 1
    15041524             ENDIF
    15051525!
    1506 !--          Calculation of total heat gains from net_sw_in through windows [W] in respect on automatic sun protection
     1526!--          Calculation of total heat gains from net_sw_in through windows [W] in respect on
     1527!--          automatic sun protection.
    15071528!--          DIN 4108 - 2 chap.8
    1508              phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off                             &
    1509                          + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win * solar_protection_on )    &
     1529             phi_sol = (   window_area_per_facade * net_sw_in * solar_protection_off               &
     1530                         + window_area_per_facade * net_sw_in * buildings(nb)%f_c_win *            &
     1531                           solar_protection_on )                                                   &
    15101532                       * buildings(nb)%g_value_win * ( 1.0_wp - params_f_f ) * params_f_w
    15111533             q_sol = phi_sol
    15121534!
    1513 !--          Calculation of the mass specific thermal load for internal and external heatsources
     1535!--          Calculation of the mass specific thermal load for internal and external heatsources.
    15141536             phi_m   = (a_m / total_area) * ( phi_ia + phi_sol )          !< [W] Eq. (C.2) with phi_ia=0,5*phi_int
    15151537             q_c_m = phi_m
    15161538!
    1517 !--          Calculation mass specific thermal load implied non thermal mass
    1518              phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )                &
    1519                        * ( phi_ia + phi_sol )                                                                       !< [W] Eq. (C.3) with phi_ia=0,5*phi_int
    1520              q_c_st = phi_st
    1521 !
    1522 !--          Calculations for deriving indoor temperature and heat flux into the wall
    1523 !--          Step 1: Indoor temperature without heating and cooling
     1539!--          Calculation mass specific thermal load implied non thermal mass.
     1540             phi_st  =   ( 1.0_wp - ( a_m / total_area ) - ( h_t_es / ( 9.1_wp * total_area ) ) )  &
     1541                       * ( phi_ia + phi_sol )                                                       !< [W] Eq. (C.3) with
     1542                                                                                                    !< phi_ia=0,5*phi_int
     1543             q_c_st = phi_st
     1544!
     1545!--          Calculations for deriving indoor temperature and heat flux into the wall.
     1546!--          Step 1: indoor temperature without heating and cooling.
    15241547!--          section C.4.1 Picture C.2 zone 3)
    15251548             phi_hc_nd = 0.0_wp
    1526              CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
     1549             CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,                  &
    15271550                                         near_facade_temperature, phi_hc_nd )
    15281551!
    1529 !--          If air temperature between border temperatures of heating and cooling, assign output variable, then ready 
    1530              IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.  theta_air <= buildings(nb)%theta_int_c_set )  THEN
     1552!--          If air temperature between border temperatures of heating and cooling, assign output
     1553!--          variable, then ready.
     1554             IF ( buildings(nb)%theta_int_h_set <= theta_air  .AND.                                &
     1555                  theta_air <= buildings(nb)%theta_int_c_set )  THEN
    15311556                phi_hc_nd_ac = 0.0_wp
    15321557                phi_hc_nd    = phi_hc_nd_ac
     
    15431568                IF ( theta_air_0 > buildings(nb)%theta_int_c_set )  THEN
    15441569                   theta_air_set = buildings(nb)%theta_int_c_set
    1545                 ELSE 
    1546                    theta_air_set = buildings(nb)%theta_int_h_set 
     1570                ELSE
     1571                   theta_air_set = buildings(nb)%theta_int_h_set
    15471572                ENDIF
    15481573
     
    15501575                phi_hc_nd_10 = 10.0_wp * floor_area_per_facade
    15511576                phi_hc_nd    = phi_hc_nd_10
    1552        
    1553                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1554                                             near_facade_temperature, phi_hc_nd )
     1577
     1578                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature,              &
     1579                                             near_facade_temperature, phi_hc_nd )
    15551580
    15561581                theta_air_10 = theta_air !< Note the temperature with 10 W/m2 of heating
    15571582
    1558                 phi_hc_nd_un = phi_hc_nd_10 * ( theta_air_set - theta_air_0 )  &
     1583                phi_hc_nd_un = phi_hc_nd_10 * ( theta_air_set - theta_air_0 )                      &
    15591584                                            / ( theta_air_10  - theta_air_0 )            !< Eq. (C.13)
    15601585!
    1561 !--             Step 3: With temperature ratio to determine the heating or cooling capacity   
    1562 !--             If necessary, limit the power to maximum power
     1586!--             Step 3: with temperature ratio to determine the heating or cooling capacity
     1587!--             If necessary, limit the power to maximum power.
    15631588!--             section C.4.1 Picture C.2 zone 2) and 4)
    15641589                buildings(nb)%phi_c_max = buildings(nb)%q_c_max * floor_area_per_facade
    15651590                buildings(nb)%phi_h_max = buildings(nb)%q_h_max * floor_area_per_facade
    1566                 IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.  phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
     1591                IF ( buildings(nb)%phi_c_max < phi_hc_nd_un  .AND.                                 &
     1592                     phi_hc_nd_un < buildings(nb)%phi_h_max )  THEN
    15671593                   phi_hc_nd_ac = phi_hc_nd_un
    15681594                   phi_hc_nd = phi_hc_nd_un
    15691595                ELSE
    15701596!
    1571 !--             Step 4: Inner temperature with maximum heating (phi_hc_nd_un positive) or cooling (phi_hc_nd_un negative)
     1597!--             Step 4: inner temperature with maximum heating (phi_hc_nd_un positive) or cooling
     1598!--                     (phi_hc_nd_un negative)
    15721599!--             section C.4.1 Picture C.2 zone 1) and 5)
    15731600                   IF ( phi_hc_nd_un > 0.0_wp )  THEN
    15741601                      phi_hc_nd_ac = buildings(nb)%phi_h_max                                         !< Limit heating
    1575                    ELSE 
     1602                   ELSE
    15761603                      phi_hc_nd_ac = buildings(nb)%phi_c_max                                         !< Limit cooling
    15771604                   ENDIF
    15781605                ENDIF
    1579                 phi_hc_nd = phi_hc_nd_ac 
     1606                phi_hc_nd = phi_hc_nd_ac
    15801607!
    15811608!--             Calculate the temperature with phi_hc_nd_ac (new)
    1582                 CALL im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
    1583                                             near_facade_temperature, phi_hc_nd )
     1609                CALL  im_calc_temperatures ( i, j, k, indoor_wall_window_temperature, &
     1610                                             near_facade_temperature, phi_hc_nd )
    15841611                theta_air_ac = theta_air
    15851612             ENDIF
     
    15871614!--          Update theta_m_t_prev
    15881615             theta_m_t_prev = theta_m_t
    1589              
     1616
    15901617             q_vent = h_v * ( theta_air - near_facade_temperature )
    15911618!
    1592 !--          Calculate the operating temperature with weighted mean of temperature of air and mean
    1593 !--          Will be used for thermal comfort calculations 
     1619!--          Calculate the operating temperature with weighted mean of temperature of air and mean.
     1620!--          Will be used for thermal comfort calculations.
    15941621             theta_op     = 0.3_wp * theta_air_ac + 0.7_wp * theta_s
    15951622!              surf_usm_v(l)%t_indoor(m) = theta_op                  !< not integrated yet
    15961623!
    1597 !--          Heat flux into the wall. Value needed in urban_surface_mod to 
     1624!--          Heat flux into the wall. Value needed in urban_surface_mod to
    15981625!--          calculate heat transfer through wall layers towards the facade
    1599              q_wall_win = h_t_ms * ( theta_s - theta_m )                       &
    1600                                     / (   facade_element_area                  &
    1601                                         - window_area_per_facade )
     1626             q_wall_win = h_t_ms * ( theta_s - theta_m )                                           &
     1627                                    / ( facade_element_area - window_area_per_facade )
    16021628             q_trans = q_wall_win * facade_element_area
    16031629!
     
    16061632             surf_usm_v(l)%iwghf_eb_window(m) = q_wall_win
    16071633!
    1608 !--          Sum up operational indoor temperature per kk-level. Further below,
    1609 !--          this temperature is reduced by MPI to one temperature per kk-level
    1610 !--          and building (processor overlapping)
     1634!--          Sum up operational indoor temperature per kk-level. Further below, this temperature is
     1635!--          reduced by MPI to one temperature per kk-level and building (processor overlapping).
    16111636             buildings(nb)%t_in_l(kk) = buildings(nb)%t_in_l(kk) + theta_op
    16121637!
    1613 !--          Calculation of waste heat
    1614 !--          Anthropogenic heat output
    1615              IF ( phi_hc_nd_ac > 0.0_wp )  THEN 
     1638!--          Calculation of waste heat.
     1639!--          Anthropogenic heat output.
     1640             IF ( phi_hc_nd_ac > 0.0_wp )  THEN
    16161641                heating_on = 1
    16171642                cooling_on = 0
    1618              ELSE 
     1643             ELSE
    16191644                heating_on = 0
    16201645                cooling_on = -1
    16211646             ENDIF
    16221647
    1623              q_waste_heat = ( phi_hc_nd * (                                    &
    1624                     buildings(nb)%params_waste_heat_h * heating_on +           &
    1625                     buildings(nb)%params_waste_heat_c * cooling_on )           &
    1626                             ) / facade_element_area !< [W/m2] , observe the directional convention in PALM!
     1648             q_waste_heat = ( phi_hc_nd * ( buildings(nb)%params_waste_heat_h * heating_on +       &
     1649                                            buildings(nb)%params_waste_heat_c * cooling_on )       &
     1650                                                    ) / facade_element_area  !< [W/m2] , observe the directional convention in
     1651                                                                             !< PALM!
    16271652             surf_usm_v(l)%waste_heat(m) = q_waste_heat
    16281653          ENDDO !< Vertical surfaces loop
     
    16311656
    16321657!
    1633 !-- Determine the mean building temperature. 
     1658!-- Determine the mean building temperature.
    16341659    DO  nb = 1, num_build
    16351660!
    1636 !--    Allocate dummy array used for summing-up facade elements. 
    1637 !--    Please note, dummy arguments are necessary as building-date type
    1638 !--    arrays are not necessarily allocated on all PEs.
     1661!--    Allocate dummy array used for summing-up facade elements.
     1662!--    Please note, dummy arguments are necessary as building-date type arrays are not necessarily
     1663!--    allocated on all PEs.
    16391664       ALLOCATE( t_in_l_send(buildings(nb)%kb_min:buildings(nb)%kb_max) )
    16401665       ALLOCATE( t_in_recv(buildings(nb)%kb_min:buildings(nb)%kb_max) )
     
    16471672
    16481673
    1649 #if defined( __parallel ) 
    1650        CALL MPI_ALLREDUCE( t_in_l_send,                                        &
    1651                            t_in_recv,                                          &
    1652                            buildings(nb)%kb_max - buildings(nb)%kb_min + 1,    &
    1653                            MPI_REAL,                                           &
    1654                            MPI_SUM,                                            &
    1655                            comm2d,                                             &
     1674#if defined( __parallel )
     1675       CALL MPI_ALLREDUCE( t_in_l_send,                                                            &
     1676                           t_in_recv,                                                              &
     1677                           buildings(nb)%kb_max - buildings(nb)%kb_min + 1,                        &
     1678                           MPI_REAL,                                                               &
     1679                           MPI_SUM,                                                                &
     1680                           comm2d,                                                                 &
    16561681                           ierr )
    16571682
    1658        IF ( ALLOCATED( buildings(nb)%t_in ) )                                  &
    1659            buildings(nb)%t_in = t_in_recv
     1683       IF ( ALLOCATED( buildings(nb)%t_in ) )  buildings(nb)%t_in = t_in_recv
    16601684#else
    1661        IF ( ALLOCATED( buildings(nb)%t_in ) )                                  &
    1662           buildings(nb)%t_in = buildings(nb)%t_in_l
     1685       IF ( ALLOCATED( buildings(nb)%t_in ) )  buildings(nb)%t_in = buildings(nb)%t_in_l
    16631686#endif
    16641687
    16651688       IF ( ALLOCATED( buildings(nb)%t_in ) )  THEN
    16661689!
    1667 !--       Average indoor temperature. Note, in case a building is completely
    1668 !--       surrounded by higher buildings, it may have no facade elements
    1669 !--       at some height levels, which will lead to a divide by zero.
     1690!--       Average indoor temperature. Note, in case a building is completely surrounded by higher
     1691!--       buildings, it may have no facade elements at some height levels, which will lead to a
     1692!--       division by zero.
    16701693          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    1671              IF ( buildings(nb)%num_facade_h(k) +                              &
    1672                   buildings(nb)%num_facade_v(k) > 0 )  THEN
    1673                 buildings(nb)%t_in(k) = buildings(nb)%t_in(k) /                &
    1674                                REAL( buildings(nb)%num_facade_h(k) +           &
    1675                                      buildings(nb)%num_facade_v(k), KIND = wp )
     1694             IF ( buildings(nb)%num_facade_h(k) + buildings(nb)%num_facade_v(k) > 0 )  THEN
     1695                buildings(nb)%t_in(k) = buildings(nb)%t_in(k) /                                    &
     1696                                        REAL( buildings(nb)%num_facade_h(k) +                      &
     1697                                              buildings(nb)%num_facade_v(k), KIND = wp )
    16761698             ENDIF
    16771699          ENDDO
    16781700!
    1679 !--       If indoor temperature is not defined because of missing facade
    1680 !--       elements, the values from the above-lying level will be taken.
    1681 !--       At least at the top of the buildings facades are defined, so that
    1682 !--       at least there an indoor temperature is defined. This information
    1683 !--       will propagate downwards the building.
     1701!--       If indoor temperature is not defined because of missing facade elements, the values from
     1702!--       the above-lying level will be taken.
     1703!--       At least at the top of the buildings facades are defined, so that at least there an indoor
     1704!--       temperature is defined. This information will propagate downwards the building.
    16841705          DO  k = buildings(nb)%kb_max-1, buildings(nb)%kb_min, -1
    1685              IF ( buildings(nb)%num_facade_h(k) +                              &
    1686                   buildings(nb)%num_facade_v(k) <= 0 )  THEN
     1706             IF ( buildings(nb)%num_facade_h(k) + buildings(nb)%num_facade_v(k) <= 0 )  THEN
    16871707                buildings(nb)%t_in(k) = buildings(nb)%t_in(k+1)
    16881708             ENDIF
    16891709          ENDDO
    16901710       ENDIF
    1691        
     1711
    16921712
    16931713!
     
    16971717
    16981718    ENDDO
    1699    
     1719
    17001720 END SUBROUTINE im_main_heatcool
    17011721
    1702 !-----------------------------------------------------------------------------!
     1722
     1723!--------------------------------------------------------------------------------------------------!
    17031724! Description:
    17041725!-------------
    17051726!> Check data output for plant canopy model
    1706 !-----------------------------------------------------------------------------!
     1727!--------------------------------------------------------------------------------------------------!
    17071728 SUBROUTINE im_check_data_output( var, unit )
    17081729
    17091730    CHARACTER (LEN=*) ::  unit   !<
    17101731    CHARACTER (LEN=*) ::  var    !<
    1711        
     1732
    17121733    SELECT CASE ( TRIM( var ) )
    1713    
    1714    
     1734
     1735
    17151736        CASE ( 'im_hf_roof')
    17161737           unit = 'W m-2'
    1717        
     1738
    17181739        CASE ( 'im_hf_wall_win' )
    17191740           unit = 'W m-2'
    1720            
     1741
    17211742        CASE ( 'im_hf_wall_win_waste' )
    17221743           unit = 'W m-2'
    1723            
     1744
    17241745        CASE ( 'im_hf_roof_waste' )
    17251746           unit = 'W m-2'
    1726        
     1747
    17271748        CASE ( 'im_t_indoor_mean' )
    17281749           unit = 'K'
    1729            
     1750
    17301751        CASE ( 'im_t_indoor_roof' )
    17311752           unit = 'K'
    1732            
     1753
    17331754        CASE ( 'im_t_indoor_wall_win' )
    17341755           unit = 'K'
    1735        
     1756
    17361757        CASE DEFAULT
    17371758           unit = 'illegal'
    1738            
     1759
    17391760    END SELECT
    1740    
     1761
    17411762 END SUBROUTINE
    17421763
    17431764
    1744 !-----------------------------------------------------------------------------!
     1765!--------------------------------------------------------------------------------------------------!
    17451766! Description:
    17461767!-------------
    17471768!> Check parameters routine for plant canopy model
    1748 !-----------------------------------------------------------------------------!
     1769!--------------------------------------------------------------------------------------------------!
    17491770 SUBROUTINE im_check_parameters
    17501771
    17511772!   USE control_parameters,
    17521773!       ONLY: message_string
    1753    
     1774
    17541775 END SUBROUTINE im_check_parameters
    17551776
    1756 !-----------------------------------------------------------------------------!
     1777
     1778!--------------------------------------------------------------------------------------------------!
    17571779! Description:
    17581780!-------------
    17591781!> Subroutine defining appropriate grid for netcdf variables.
    17601782!> It is called from subroutine netcdf.
    1761 !-----------------------------------------------------------------------------!
     1783!--------------------------------------------------------------------------------------------------!
    17621784 SUBROUTINE im_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
    17631785
    1764    
    1765    CHARACTER (LEN=*), INTENT(IN)  ::  var
    1766    LOGICAL, INTENT(OUT)           ::  found
    1767    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x
    1768    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y
    1769    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z
    1770    
    1771    found   = .TRUE.
    1772    
     1786    CHARACTER (LEN=*), INTENT(OUT) ::  grid_x
     1787    CHARACTER (LEN=*), INTENT(OUT) ::  grid_y
     1788    CHARACTER (LEN=*), INTENT(OUT) ::  grid_z
     1789    CHARACTER (LEN=*), INTENT(IN)  ::  var
     1790
     1791    LOGICAL, INTENT(OUT)           ::  found
     1792
     1793
     1794    found   = .TRUE.
    17731795!
    17741796!-- Check for the grid
     
    17901812          grid_y = 'y'
    17911813          grid_z = 'zw'
    1792          
     1814
    17931815       CASE DEFAULT
    17941816          found  = .FALSE.
     
    17971819          grid_z = 'none'
    17981820    END SELECT
    1799    
     1821
    18001822 END SUBROUTINE im_define_netcdf_grid
    18011823
    1802 !------------------------------------------------------------------------------!
     1824
     1825!--------------------------------------------------------------------------------------------------!
    18031826! Description:
    18041827! ------------
    18051828!> Subroutine defining 3D output variables
    1806 !------------------------------------------------------------------------------!
    1807  SUBROUTINE im_data_output_3d( av, variable, found, local_pf, fill_value,      &
    1808                                nzb_do, nzt_do )
     1829!--------------------------------------------------------------------------------------------------!
     1830 SUBROUTINE im_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    18091831
    18101832    USE indices
     
    18121834    USE kinds
    18131835
    1814     CHARACTER (LEN=*) ::  variable !< 
    1815 
    1816     INTEGER(iwp) ::  av    !< 
    1817     INTEGER(iwp) ::  i     !< 
    1818     INTEGER(iwp) ::  j     !< 
    1819     INTEGER(iwp) ::  k     !< 
     1836    CHARACTER (LEN=*) ::  variable !<
     1837
     1838    INTEGER(iwp) ::  av    !<
     1839    INTEGER(iwp) ::  i     !<
     1840    INTEGER(iwp) ::  j     !<
     1841    INTEGER(iwp) ::  k     !<
    18201842    INTEGER(iwp) ::  l     !<
    1821     INTEGER(iwp) ::  m     !< 
    1822     INTEGER(iwp) ::  nb    !< index of the building in the building data structure 
     1843    INTEGER(iwp) ::  m     !<
     1844    INTEGER(iwp) ::  nb    !< index of the building in the building data structure
    18231845    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
    18241846    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    1825    
    1826     LOGICAL      ::  found !< 
     1847
     1848    LOGICAL      ::  found !<
    18271849
    18281850    REAL(wp), INTENT(IN) ::  fill_value !< value for the _FillValue attribute
    18291851
    1830     REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !< 
    1831    
     1852    REAL(sp), DIMENSION(nxl:nxr,nys:nyn,nzb_do:nzt_do) ::  local_pf !<
     1853
    18321854    local_pf = fill_value
    1833    
     1855
    18341856    found = .TRUE.
    1835    
     1857
    18361858    SELECT CASE ( TRIM( variable ) )
    18371859!
    1838 !--     Output of indoor temperature. All grid points within the building are
    1839 !--     filled with values, while atmospheric grid points are set to _FillValues.
     1860!--     Output of indoor temperature. All grid points within the building are filled with values,
     1861!--     while atmospheric grid points are set to _FillValues.
    18401862        CASE ( 'im_t_indoor_mean' )
    18411863           IF ( av == 0 ) THEN
     
    18441866                    IF ( building_id_f%var(j,i) /= building_id_f%fill )  THEN
    18451867!
    1846 !--                    Determine index of the building within the building data structure.
    1847                        nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ),   &
    1848                                     DIM = 1 )
     1868!--                    Determine index of the building within the building data structure.
     1869                       nb = MINLOC( ABS( buildings(:)%id - building_id_f%var(j,i) ), DIM=1 )
    18491870                       IF ( buildings(nb)%on_pe )  THEN
    18501871!
    1851 !--                       Write mean building temperature onto output array. Please note,
    1852 !--                       in contrast to many other loops in the output, the vertical
    1853 !--                       bounds are determined by the lowest and hightest vertical index
    1854 !--                       occupied by the building.
     1872!--                       Write mean building temperature onto output array. Please note, in
     1873!--                       contrast to many other loops in the output, the vertical bounds are
     1874!--                       determined by the lowest and hightest vertical index occupied by the
     1875!--                       building.
    18551876                          DO  k = buildings(nb)%kb_min, buildings(nb)%kb_max
    18561877                             local_pf(i,j,k) = buildings(nb)%t_in(k)
     
    18601881                 ENDDO
    18611882              ENDDO
    1862            ENDIF 
     1883           ENDIF
    18631884
    18641885        CASE ( 'im_hf_roof' )
    1865            IF ( av == 0 ) THEN
     1886           IF ( av == 0 )  THEN
    18661887              DO  m = 1, surf_usm_h%ns
    18671888                 i = surf_usm_h%i(m) !+ surf_usm_h%ioff
     
    18701891                 local_pf(i,j,k) = surf_usm_h%iwghf_eb(m)
    18711892              ENDDO
    1872            ENDIF 
     1893           ENDIF
    18731894
    18741895        CASE ( 'im_hf_roof_waste' )
    1875            IF ( av == 0 ) THEN
    1876               DO m = 1, surf_usm_h%ns 
     1896           IF ( av == 0 )  THEN
     1897              DO m = 1, surf_usm_h%ns
    18771898                 i = surf_usm_h%i(m) !+ surf_usm_h%ioff
    18781899                 j = surf_usm_h%j(m) !+ surf_usm_h%joff
     
    18831904
    18841905       CASE ( 'im_hf_wall_win' )
    1885            IF ( av == 0 ) THEN
     1906           IF ( av == 0 )  THEN
    18861907              DO l = 0, 3
    18871908                 DO m = 1, surf_usm_v(l)%ns
     
    18951916
    18961917        CASE ( 'im_hf_wall_win_waste' )
    1897            IF ( av == 0 ) THEN
     1918           IF ( av == 0 )  THEN
    18981919              DO l = 0, 3
    1899                  DO m = 1, surf_usm_v(l)%ns 
     1920                 DO m = 1, surf_usm_v(l)%ns
    19001921                    i = surf_usm_v(l)%i(m) !+ surf_usm_v(l)%ioff
    19011922                    j = surf_usm_v(l)%j(m) !+ surf_usm_v(l)%joff
    19021923                    k = surf_usm_v(l)%k(m) !+ surf_usm_v(l)%koff
    1903                     local_pf(i,j,k) =  surf_usm_v(l)%waste_heat(m) 
     1924                    local_pf(i,j,k) =  surf_usm_v(l)%waste_heat(m)
    19041925                 ENDDO
    19051926              ENDDO
     
    19101931
    19111932!         CASE ( 'im_t_indoor_roof' )
    1912 !            IF ( av == 0 ) THEN
     1933!            IF ( av == 0 )  THEN
    19131934!               DO  m = 1, surf_usm_h%ns
    19141935!                   i = surf_usm_h%i(m) !+ surf_usm_h%ioff
     
    19181939!               ENDDO
    19191940!            ENDIF
    1920 ! 
     1941!
    19211942!         CASE ( 'im_t_indoor_wall_win' )
    1922 !            IF ( av == 0 ) THEN           
     1943!            IF ( av == 0 )  THEN
    19231944!               DO l = 0, 3
    19241945!                  DO m = 1, surf_usm_v(l)%ns
     
    19331954        CASE DEFAULT
    19341955           found = .FALSE.
    1935            
    1936     END SELECT   
    1937 
    1938  END SUBROUTINE im_data_output_3d         
    1939 !------------------------------------------------------------------------------!
     1956
     1957    END SELECT
     1958
     1959 END SUBROUTINE im_data_output_3d
     1960
     1961
     1962!--------------------------------------------------------------------------------------------------!
    19401963! Description:
    19411964! ------------
    19421965!> Parin for &indoor_parameters for indoor model
    1943 !------------------------------------------------------------------------------!
     1966!--------------------------------------------------------------------------------------------------!
    19441967 SUBROUTINE im_parin
    1945    
    1946     USE control_parameters,                                                    &
     1968
     1969    USE control_parameters,                                                                        &
    19471970        ONLY:  indoor_model
    19481971
     
    19511974
    19521975    NAMELIST /indoor_parameters/  initial_indoor_temperature
     1976
    19531977
    19541978!
     
    19561980    REWIND ( 11 )
    19571981    line = ' '
    1958     DO   WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
     1982    DO  WHILE ( INDEX( line, '&indoor_parameters' ) == 0 )
    19591983       READ ( 11, '(A)', END=10 )  line
    19601984    ENDDO
     
    19802004
    19812005 10 CONTINUE
    1982    
     2006
    19832007 END SUBROUTINE im_parin
    19842008
  • palm/trunk/SOURCE/inflow_turbulence.f90

    r4429 r4646  
    11!> @file inflow_turbulence.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/>.
     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/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4429 2020-02-27 15:24:30Z raasch
    2729! bugfix: cpp-directives added for serial mode
    28 ! 
     30!
    2931! 4360 2020-01-07 11:25:50Z suehring
    3032! use y_shift instead of old parameter recycling_yshift
    31 ! 
     33!
    3234! 4297 2019-11-21 10:37:50Z oliver.maas
    33 ! changed recycling_yshift so that the y-shift can be a multiple of PE
    34 ! instead of y-shift of a half domain width
    35 ! 
     35! changed recycling_yshift so that the y-shift can be a multiple of PE instead of y-shift of a half
     36! domain width
     37!
    3638! 4183 2019-08-23 07:33:16Z oliver.maas
    37 ! simplified steering of recycling of absolute values by initialization
    38 ! parameter recycling_method_for_thermodynamic_quantities
    39 ! 
     39! simplified steering of recycling of absolute values by initialization parameter
     40! recycling_method_for_thermodynamic_quantities
     41!
    4042! 4182 2019-08-22 15:20:23Z scharf
    4143! Corrected "Former revisions" section
    42 ! 
     44!
    4345! 4172 2019-08-20 11:55:33Z oliver.maas
    4446! added optional recycling of absolute values for pt and q
    45 ! 
     47!
    4648! 3655 2019-01-07 16:51:22Z knoop
    4749! Corrected "Former revisions" section
     
    5153! Description:
    5254! ------------
    53 !> Imposing turbulence at the respective inflow using the turbulence
    54 !> recycling method of Kataoka and Mizuno (2002).
    55 !------------------------------------------------------------------------------!
     55!> Imposing turbulence at the respective inflow using the turbulence recycling method of
     56!> Kataoka and Mizuno (2002).
     57!--------------------------------------------------------------------------------------------------!
    5658 SUBROUTINE inflow_turbulence
    57  
    58 
    59     USE arrays_3d,                                                             &
     59
     60
     61    USE arrays_3d,                                                                                 &
    6062        ONLY:  e, inflow_damping_factor, mean_inflow_profiles, pt, q, s, u, v, w
    61        
    62 #if defined( __parallel )
    63     USE control_parameters,                                                    &
    64         ONLY:  humidity, passive_scalar, recycling_plane, y_shift,             &
    65                recycling_method_for_thermodynamic_quantities
     63
     64#if defined( __parallel )
     65    USE control_parameters,                                                                        &
     66        ONLY:  humidity, passive_scalar, recycling_method_for_thermodynamic_quantities,            &
     67               recycling_plane, y_shift
     68
    6669#else
    67     USE control_parameters,                                                    &
    68         ONLY:  humidity, passive_scalar, recycling_plane,                      &
    69                recycling_method_for_thermodynamic_quantities
    70 #endif
    71        
    72     USE cpulog,                                                                &
     70    USE control_parameters,                                                                        &
     71        ONLY:  humidity, passive_scalar, recycling_method_for_thermodynamic_quantities,            &
     72               recycling_plane
     73
     74#endif
     75
     76    USE cpulog,                                                                                    &
    7377        ONLY:  cpu_log, log_point
    74        
    75     USE indices,                                                               &
     78
     79    USE indices,                                                                                   &
    7680        ONLY:  nbgp, nxl, ny, nyn, nys, nyng, nysg, nzb, nzt
    77        
     81
    7882    USE kinds
    79    
     83
    8084    USE pegrid
    8185
    8286
    8387    IMPLICIT NONE
    84    
     88
    8589    INTEGER(iwp) ::  i        !< loop index
    8690    INTEGER(iwp) ::  j        !< loop index
     
    9498#endif
    9599
    96     REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp)           ::                         &
    97        avpr               !< stores averaged profiles at recycling plane
    98     REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp)           ::                         &
    99        avpr_l             !< auxiliary variable to calculate avpr
    100     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    101        inflow_dist        !< turbulence signal of vars, added at inflow boundary
    102 #if defined( __parallel )
    103     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    104        local_inflow_dist  !< auxiliary variable for inflow_dist, used for y-shift
    105 #endif
    106    
     100    REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp) ::  avpr               !< stores averaged profiles at recycling plane
     101    REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp) ::  avpr_l             !< auxiliary variable to calculate avpr
     102
     103    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::  inflow_dist        !< turbulence signal of vars, added at inflow boundary
     104#if defined( __parallel )
     105    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::  local_inflow_dist  !< auxiliary variable for inflow_dist, used for y-shift
     106#endif
     107
    107108    CALL cpu_log( log_point(40), 'inflow_turbulence', 'start' )
    108    
     109
    109110!
    110111!-- Carry out spanwise averaging in the recycling plane
     
    119120#if defined( __parallel )
    120121    IF ( myidx == id_recycling )  THEN
    121        
     122
    122123       DO  l = 1, nbgp
    123124          DO  j = nys, nyn
     
    129130                avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i)
    130131                avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i)
    131                 IF ( humidity )                                                &
    132                    avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
    133                 IF ( passive_scalar )                                          &
    134                    avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
     132                IF ( humidity )  avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
     133                IF ( passive_scalar )  avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
    135134
    136135             ENDDO
     
    143142!-- Now, averaging over all PEs
    144143    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    145     CALL MPI_ALLREDUCE( avpr_l(nzb,1,1), avpr(nzb,1,1), ngp_pr, MPI_REAL,      &
    146                         MPI_SUM, comm2d, ierr )
     144    CALL MPI_ALLREDUCE( avpr_l(nzb,1,1), avpr(nzb,1,1), ngp_pr, MPI_REAL, MPI_SUM, comm2d, ierr )
    147145
    148146#else
     
    156154             avpr_l(k,4,l) = avpr_l(k,4,l) + pt(k,j,i)
    157155             avpr_l(k,5,l) = avpr_l(k,5,l) + e(k,j,i)
    158              IF ( humidity )                                                   &
    159                 avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
    160              IF ( passive_scalar )                                             &
    161                 avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
    162 
    163           ENDDO
    164        ENDDO
    165        i = i + 1
     156             IF ( humidity )  avpr_l(k,6,l) = avpr_l(k,6,l) + q(k,j,i)
     157             IF ( passive_scalar )  avpr_l(k,7,l) = avpr_l(k,7,l) + s(k,j,i)
     158
     159          ENDDO
     160       ENDDO
     161       i = i + 1
    166162    ENDDO
    167    
     163
    168164    avpr = avpr_l
    169165#endif
     
    171167    avpr = avpr / ( ny + 1 )
    172168!
    173 !-- Calculate the disturbances at the recycling plane
    174 !-- for recycling of absolute quantities, the disturbance is defined as the absolute value
    175 !-- (and not as the deviation from the mean profile)
     169!-- Calculate the disturbances at the recycling plane for recycling of absolute quantities, the
     170!-- disturbance is defined as the absolute value (and not as the deviation from the mean profile).
    176171    i = recycling_plane
    177172
     
    184179                inflow_dist(k,j,2,l) = v(k,j,i)   - avpr(k,2,l)
    185180                inflow_dist(k,j,3,l) = w(k,j,i)   - avpr(k,3,l)
    186                 IF ( TRIM( recycling_method_for_thermodynamic_quantities )     &
    187                    == 'turbulent_fluctuation' )  THEN
     181                IF ( TRIM( recycling_method_for_thermodynamic_quantities )                         &
     182                     == 'turbulent_fluctuation' )  THEN
    188183                   inflow_dist(k,j,4,l) = pt(k,j,i) - avpr(k,4,l)
    189                 ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities ) &
    190                    == 'absolute_value' )  THEN
     184                ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                     &
     185                         == 'absolute_value' )  THEN
    191186                   inflow_dist(k,j,4,l) = pt(k,j,i)
    192187                ENDIF
    193188                inflow_dist(k,j,5,l) = e(k,j,i)   - avpr(k,5,l)
    194189                IF ( humidity ) THEN
    195                    IF ( TRIM( recycling_method_for_thermodynamic_quantities )  &
    196                       == 'turbulent_fluctuation' )  THEN
     190                   IF ( TRIM( recycling_method_for_thermodynamic_quantities )                      &
     191                        == 'turbulent_fluctuation' )  THEN
    197192                      inflow_dist(k,j,6,l) = q(k,j,i) - avpr(k,6,l)
    198                    ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )  &
    199                       == 'absolute_value' )  THEN
     193                   ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                  &
     194                            == 'absolute_value' )  THEN
    200195                      inflow_dist(k,j,6,l) = q(k,j,i)
    201196                   ENDIF
    202197                ENDIF
    203                 IF ( passive_scalar )                                          &
     198                IF ( passive_scalar )                                                              &
    204199                   inflow_dist(k,j,7,l) = s(k,j,i) - avpr(k,7,l)
    205200            ENDDO
     
    216211             inflow_dist(k,j,2,l) = v(k,j,i)   - avpr(k,2,l)
    217212             inflow_dist(k,j,3,l) = w(k,j,i)   - avpr(k,3,l)
    218              IF ( TRIM( recycling_method_for_thermodynamic_quantities )        &
     213             IF ( TRIM( recycling_method_for_thermodynamic_quantities )                            &
    219214                   == 'turbulent_fluctuation' )  THEN
    220215                inflow_dist(k,j,4,l) = pt(k,j,i) - avpr(k,4,l)
    221              ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )    &
    222                    == 'absolute_value' )  THEN
     216             ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                        &
     217                      == 'absolute_value' )  THEN
    223218                inflow_dist(k,j,4,l) = pt(k,j,i)
    224219             ENDIF
    225220             inflow_dist(k,j,5,l) = e(k,j,i)   - avpr(k,5,l)
    226221             IF ( humidity )  THEN
    227                 IF ( TRIM( recycling_method_for_thermodynamic_quantities )     &
    228                       == 'turbulent_fluctuation' )  THEN
     222                IF ( TRIM( recycling_method_for_thermodynamic_quantities )                         &
     223                     == 'turbulent_fluctuation' )  THEN
    229224                   inflow_dist(k,j,6,l) = q(k,j,i) - avpr(k,6,l)
    230                 ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities ) &
    231                       == 'absolute_value' )  THEN
     225                ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                     &
     226                         == 'absolute_value' )  THEN
    232227                   inflow_dist(k,j,6,l) = q(k,j,i)
    233228                ENDIF
    234229             ENDIF
    235              IF ( passive_scalar )                                             &
     230             IF ( passive_scalar )                                                                 &
    236231                inflow_dist(k,j,7,l) = s(k,j,i) - avpr(k,7,l)
    237              
     232
    238233          ENDDO
    239234       ENDDO
     
    247242    IF ( myidx == id_recycling  .AND.  myidx /= id_inflow )  THEN
    248243
    249        CALL MPI_SEND( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL,            &
    250                       id_inflow, 1, comm1dx, ierr )
     244       CALL MPI_SEND( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, id_inflow, 1, comm1dx, ierr )
    251245
    252246    ELSEIF ( myidx /= id_recycling  .AND.  myidx == id_inflow )  THEN
    253247
    254248       inflow_dist = 0.0_wp
    255        CALL MPI_RECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL,            &
    256                       id_recycling, 1, comm1dx, status, ierr )
     249       CALL MPI_RECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, id_recycling, 1, comm1dx,      &
     250                      status, ierr )
    257251
    258252    ENDIF
     
    262256!-- Shift inflow_dist in positive y direction by a number of
    263257!-- PEs equal to y_shift
    264     IF ( ( y_shift /= 0 ) .AND. myidx == id_inflow ) THEN
    265 
    266 !
    267 !--    Calculate the ID of the PE which sends data to this PE (prev) and of the
    268 !--    PE which receives data from this PE (next).
     258    IF ( ( y_shift /= 0 )  .AND.  myidx == id_inflow ) THEN
     259
     260!
     261!--    Calculate the ID of the PE which sends data to this PE (prev) and of the PE which receives
     262!--    data from this PE (next).
    269263       prev = MODULO(myidy - y_shift , pdims(2))
    270264       next = MODULO(myidy + y_shift , pdims(2))
    271        
     265
    272266       local_inflow_dist = 0.0_wp
    273267
    274        CALL MPI_SENDRECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL,        &
    275                           next, 1, local_inflow_dist(nzb,nysg,1,1), ngp_ifd,   &
    276                           MPI_REAL, prev, 1, comm1dy, status, ierr )
     268       CALL MPI_SENDRECV( inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, next, 1,                   &
     269                          local_inflow_dist(nzb,nysg,1,1), ngp_ifd, MPI_REAL, prev, 1, comm1dy,    &
     270                          status, ierr )
    277271
    278272       inflow_dist = local_inflow_dist
     
    289283          DO  k = nzb, nzt + 1
    290284
    291              u(k,j,-nbgp+1:0) = mean_inflow_profiles(k,1) +                    &
    292                         inflow_dist(k,j,1,1:nbgp) * inflow_damping_factor(k)
    293              v(k,j,-nbgp:-1)  = mean_inflow_profiles(k,2) +                    &
    294                         inflow_dist(k,j,2,1:nbgp) * inflow_damping_factor(k)
    295              w(k,j,-nbgp:-1)  =                                                &
    296                         inflow_dist(k,j,3,1:nbgp) * inflow_damping_factor(k)
    297              IF ( TRIM( recycling_method_for_thermodynamic_quantities )        &
     285             u(k,j,-nbgp+1:0) = mean_inflow_profiles(k,1) +                                        &
     286                                inflow_dist(k,j,1,1:nbgp) * inflow_damping_factor(k)
     287             v(k,j,-nbgp:-1)  = mean_inflow_profiles(k,2) +                                        &
     288                                inflow_dist(k,j,2,1:nbgp) * inflow_damping_factor(k)
     289             w(k,j,-nbgp:-1)  = inflow_dist(k,j,3,1:nbgp) * inflow_damping_factor(k)
     290             IF ( TRIM( recycling_method_for_thermodynamic_quantities )                            &
    298291                   == 'turbulent_fluctuation' )  THEN
    299                 pt(k,j,-nbgp:-1) = mean_inflow_profiles(k,4) +                 &
    300                 inflow_dist(k,j,4,1:nbgp) * inflow_damping_factor(k)
    301              ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )    &
    302                    == 'absolute_value' )  THEN
     292                pt(k,j,-nbgp:-1) = mean_inflow_profiles(k,4) +                                     &
     293                                   inflow_dist(k,j,4,1:nbgp) * inflow_damping_factor(k)
     294             ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                        &
     295                      == 'absolute_value' )  THEN
    303296                pt(k,j,-nbgp:-1) = inflow_dist(k,j,4,1:nbgp)
    304297             ENDIF
    305              e(k,j,-nbgp:-1)  = mean_inflow_profiles(k,5) +                    &
    306                         inflow_dist(k,j,5,1:nbgp) * inflow_damping_factor(k)
     298             e(k,j,-nbgp:-1)  = mean_inflow_profiles(k,5) +                                        &
     299                                inflow_dist(k,j,5,1:nbgp) * inflow_damping_factor(k)
    307300             e(k,j,-nbgp:-1)  = MAX( e(k,j,-nbgp:-1), 0.0_wp )
    308301             IF ( humidity )  THEN
    309                 IF ( TRIM( recycling_method_for_thermodynamic_quantities )     &
     302                IF ( TRIM( recycling_method_for_thermodynamic_quantities )                         &
    310303                      == 'turbulent_fluctuation' )  THEN
    311                    q(k,j,-nbgp:-1)  = mean_inflow_profiles(k,6) +              &
    312                       inflow_dist(k,j,6,1:nbgp) * inflow_damping_factor(k)
    313                 ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities ) &
    314                       == 'absolute_value' )  THEN
     304                   q(k,j,-nbgp:-1)  = mean_inflow_profiles(k,6) +                                  &
     305                                      inflow_dist(k,j,6,1:nbgp) * inflow_damping_factor(k)
     306                ELSEIF ( TRIM( recycling_method_for_thermodynamic_quantities )                     &
     307                         == 'absolute_value' )  THEN
    315308                   q(k,j,-nbgp:-1)  = inflow_dist(k,j,6,1:nbgp)
    316309                ENDIF
    317310             ENDIF
    318              IF ( passive_scalar )                                             &
    319                 s(k,j,-nbgp:-1)  = mean_inflow_profiles(k,7) +                 &
    320                         inflow_dist(k,j,7,1:nbgp) * inflow_damping_factor(k)
    321                        
    322           ENDDO
    323        ENDDO
    324 
    325     ENDIF
    326 
    327 
    328     CALL cpu_log( log_point(40), 'inflow_turbulence', 'stop' )
     311             IF ( passive_scalar )                                                                 &
     312                s(k,j,-nbgp:-1)  = mean_inflow_profiles(k,7) +                                     &
     313                                   inflow_dist(k,j,7,1:nbgp) * inflow_damping_factor(k)
     314
     315          ENDDO
     316       ENDDO
     317
     318    ENDIF
     319
     320
     321    CALL  cpu_log( log_point(40), 'inflow_turbulence', 'stop' )
    329322
    330323
Note: See TracChangeset for help on using the changeset viewer.