Ignore:
Timestamp:
May 18, 2020 3:23:29 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4444 r4540  
    11!> @file timestep.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!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
    21 ! ------------------
     21! -----------------
    2222!
    2323!
     
    2525! -----------------
    2626! $Id$
    27 ! bugfix: cpp-directives for serial mode added
    28 !
     27! File re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4444 2020-03-05 15:59:50Z raasch
     31! Bugfix: cpp-directives for serial mode added
     32!
    2933! 4360 2020-01-07 11:25:50Z suehring
    3034! Added missing OpenMP directives
    31 ! 
     35!
    3236! 4233 2019-09-20 09:55:54Z knoop
    3337! OpenACC data update host removed
    34 ! 
     38!
    3539! 4182 2019-08-22 15:20:23Z scharf
    3640! Corrected "Former revisions" section
    37 ! 
     41!
    3842! 4101 2019-07-17 15:14:26Z gronemeier
    39 ! - consider 2*Km within diffusion criterion as Km is considered twice within
    40 !   the diffusion of e,
    41 ! - in RANS mode, instead of considering each wind component individually use
    42 !   the wind speed of 3d wind vector in CFL criterion
    43 ! - do not limit the increase of dt based on its previous value in RANS mode
     43! - Consider 2*Km within diffusion criterion as Km is considered twice within the diffusion of e,
     44! - in RANS mode, instead of considering each wind component individually use the wind speed of 3d
     45!   wind vector in CFL criterion
     46! - Do not limit the increase of dt based on its previous value in RANS mode
    4447!
    4548! 3658 2019-01-07 20:28:54Z knoop
     
    5356! ------------
    5457!> Compute the time step under consideration of the FCL and diffusion criterion.
    55 !------------------------------------------------------------------------------!
     58!--------------------------------------------------------------------------------------------------!
    5659 SUBROUTINE timestep
    57  
    58 
    59     USE arrays_3d,                                                             &
    60         ONLY:  dzu, dzw, kh, km, u, u_stokes_zu, v, v_stokes_zu, w
    61 
    62     USE control_parameters,                                                    &
    63         ONLY:  cfl_factor, dt_3d, dt_fixed, dt_max, galilei_transformation,    &
    64                message_string, rans_mode, stop_dt, timestep_reason, u_gtrans,  &
    65                use_ug_for_galilei_tr, v_gtrans
    66 
    67 #if defined( __parallel )
    68     USE control_parameters,                                                    &
    69         ONLY:  coupling_mode, terminate_coupled, terminate_coupled_remote
    70 #endif
    71 
    72     USE cpulog,                                                                &
    73         ONLY:  cpu_log, log_point
    74 
    75     USE grid_variables,                                                        &
    76         ONLY:  dx, dx2, dy, dy2
    77 
    78     USE indices,                                                               &
    79         ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
     60
     61
     62    USE arrays_3d,                                                                                 &
     63        ONLY:  dzu,                                                                                &
     64               dzw,                                                                                &
     65               kh,                                                                                 &
     66               km,                                                                                 &
     67               u,                                                                                  &
     68               u_stokes_zu,                                                                        &
     69               v,                                                                                  &
     70               v_stokes_zu,                                                                        &
     71               w
     72
     73    USE control_parameters,                                                                        &
     74        ONLY:  cfl_factor,                                                                         &
     75               dt_3d,                                                                              &
     76               dt_fixed,                                                                           &
     77               dt_max,                                                                             &
     78               galilei_transformation,                                                             &
     79               message_string,                                                                     &
     80               rans_mode,                                                                          &
     81               stop_dt,                                                                            &
     82               timestep_reason,                                                                    &
     83               u_gtrans,                                                                           &
     84               use_ug_for_galilei_tr,                                                              &
     85               v_gtrans
     86
     87#if defined( __parallel )
     88    USE control_parameters,                                                                        &
     89        ONLY:  coupling_mode,                                                                      &
     90               terminate_coupled,                                                                  &
     91               terminate_coupled_remote
     92#endif
     93
     94    USE cpulog,                                                                                    &
     95        ONLY:  cpu_log,                                                                            &
     96               log_point
     97
     98    USE grid_variables,                                                                            &
     99        ONLY:  dx,                                                                                 &
     100               dx2,                                                                                &
     101               dy,                                                                                 &
     102               dy2
     103
     104    USE indices,                                                                                   &
     105        ONLY:  nxl,                                                                                &
     106               nxlg,                                                                               &
     107               nxr,                                                                                &
     108               nxrg,                                                                               &
     109               nyn,                                                                                &
     110               nyng,                                                                               &
     111               nys,                                                                                &
     112               nysg,                                                                               &
     113               nzb,                                                                                &
     114               nzt
    80115
    81116    USE interfaces
     
    83118    USE kinds
    84119
    85     USE bulk_cloud_model_mod,                                                  &
     120    USE bulk_cloud_model_mod,                                                                      &
    86121        ONLY:  dt_precipitation
    87122
    88123    USE pegrid
    89124
    90     USE pmc_interface,                                                         &
     125    USE pmc_interface,                                                                             &
    91126        ONLY:  nested_run
    92127
    93     USE statistics,                                                            &
    94         ONLY:  flow_statistics_called, hom, u_max, u_max_ijk, v_max, v_max_ijk,&
    95                w_max, w_max_ijk
    96 
    97 #if defined( __parallel )
    98     USE vertical_nesting_mod,                                                  &
    99         ONLY:  vnested, vnest_timestep_sync
     128    USE statistics,                                                                                &
     129        ONLY:  flow_statistics_called,                                                             &
     130               hom,                                                                                &
     131               u_max,                                                                              &
     132               u_max_ijk,                                                                          &
     133               v_max,                                                                              &
     134               v_max_ijk,                                                                          &
     135               w_max,                                                                              &
     136               w_max_ijk
     137
     138#if defined( __parallel )
     139    USE vertical_nesting_mod,                                                                      &
     140        ONLY:  vnested,                                                                            &
     141               vnest_timestep_sync
    100142#endif
    101143
    102144    IMPLICIT NONE
    103145
    104     INTEGER(iwp) ::  i !<
    105     INTEGER(iwp) ::  j !<
    106     INTEGER(iwp) ::  k !<
     146    INTEGER(iwp) ::  i  !<
     147    INTEGER(iwp) ::  j  !<
     148    INTEGER(iwp) ::  k  !<
    107149    INTEGER(iwp) ::  km_max_ijk(3) = -1  !< index values (i,j,k) of location where km_max occurs
    108150    INTEGER(iwp) ::  kh_max_ijk(3) = -1  !< index values (i,j,k) of location where kh_max occurs
    109151
    110     LOGICAL ::  stop_dt_local !< local switch for controlling the time stepping
    111 
    112     REAL(wp) ::  div               !<
    113     REAL(wp) ::  dt_diff           !<
    114     REAL(wp) ::  dt_diff_l         !<
    115     REAL(wp) ::  dt_u              !<
    116     REAL(wp) ::  dt_u_l            !<
    117     REAL(wp) ::  dt_v              !<
    118     REAL(wp) ::  dt_v_l            !<
    119     REAL(wp) ::  dt_w              !<
    120     REAL(wp) ::  dt_w_l            !<
    121     REAL(wp) ::  km_max            !< maximum of Km in entire domain
    122     REAL(wp) ::  kh_max            !< maximum of Kh in entire domain
    123     REAL(wp) ::  u_gtrans_l        !<
    124     REAL(wp) ::  v_gtrans_l        !<
    125  
    126     REAL(wp), DIMENSION(2)         ::  uv_gtrans_l !<
    127 #if defined( __parallel )
    128     REAL(wp), DIMENSION(2)         ::  uv_gtrans   !<
    129     REAL(wp), DIMENSION(3)         ::  reduce      !<
    130     REAL(wp), DIMENSION(3)         ::  reduce_l    !<
    131 #endif
    132     REAL(wp), DIMENSION(nzb+1:nzt) ::  dxyz2_min   !< 
     152    LOGICAL ::  stop_dt_local  !< local switch for controlling the time stepping
     153
     154    REAL(wp) ::  div         !<
     155    REAL(wp) ::  dt_diff     !<
     156    REAL(wp) ::  dt_diff_l   !<
     157    REAL(wp) ::  dt_u        !<
     158    REAL(wp) ::  dt_u_l      !<
     159    REAL(wp) ::  dt_v        !<
     160    REAL(wp) ::  dt_v_l      !<
     161    REAL(wp) ::  dt_w        !<
     162    REAL(wp) ::  dt_w_l      !<
     163    REAL(wp) ::  km_max      !< maximum of Km in entire domain
     164    REAL(wp) ::  kh_max      !< maximum of Kh in entire domain
     165    REAL(wp) ::  u_gtrans_l  !<
     166    REAL(wp) ::  v_gtrans_l  !<
     167
     168    REAL(wp), DIMENSION(2)         ::  uv_gtrans_l  !<
     169#if defined( __parallel )
     170    REAL(wp), DIMENSION(2)         ::  uv_gtrans    !<
     171    REAL(wp), DIMENSION(3)         ::  reduce       !<
     172    REAL(wp), DIMENSION(3)         ::  reduce_l     !<
     173#endif
     174    REAL(wp), DIMENSION(nzb+1:nzt) ::  dxyz2_min    !<
    133175    !$ACC DECLARE CREATE(dxyz2_min)
    134176
     
    137179
    138180!
    139 !-- In case of Galilei-transform not using the geostrophic wind as translation
    140 !-- velocity, compute the volume-averaged horizontal velocity components, which
    141 !-- will then be subtracted from the horizontal wind for the time step and
    142 !-- horizontal advection routines.
     181!-- In case of Galilei-transform not using the geostrophic wind as translation velocity, compute the
     182!-- volume-averaged horizontal velocity components, which will then be subtracted from the
     183!-- horizontal wind for the time step and horizontal advection routines.
    143184    IF ( galilei_transformation  .AND. .NOT.  use_ug_for_galilei_tr )  THEN
    144185       IF ( flow_statistics_called )  THEN
    145186!
    146 !--       Horizontal averages already existent, just need to average them
    147 !--       vertically.
     187!--       Horizontal averages already existent, just need to average them vertically.
    148188          u_gtrans = 0.0_wp
    149189          v_gtrans = 0.0_wp
     
    152192             v_gtrans = v_gtrans + hom(k,1,2,0)
    153193          ENDDO
    154           u_gtrans = u_gtrans / REAL( nzt - nzb, KIND=wp )
    155           v_gtrans = v_gtrans / REAL( nzt - nzb, KIND=wp )
     194          u_gtrans = u_gtrans / REAL( nzt - nzb, KIND = wp )
     195          v_gtrans = v_gtrans / REAL( nzt - nzb, KIND = wp )
    156196       ELSE
    157197!
     
    167207             ENDDO
    168208          ENDDO
    169           uv_gtrans_l(1) = u_gtrans_l /                                        &
    170                            REAL( (nxr-nxl+1)*(nyn-nys+1)*(nzt-nzb), KIND=wp )
    171           uv_gtrans_l(2) = v_gtrans_l /                                        &
    172                            REAL( (nxr-nxl+1)*(nyn-nys+1)*(nzt-nzb), KIND=wp )
     209          uv_gtrans_l(1) = u_gtrans_l / REAL( (nxr-nxl+1) * (nyn-nys+1) * (nzt-nzb), KIND = wp )
     210          uv_gtrans_l(2) = v_gtrans_l / REAL( (nxr-nxl+1) * (nyn-nys+1) * (nzt-nzb), KIND = wp )
    173211#if defined( __parallel )
    174212          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    175           CALL MPI_ALLREDUCE( uv_gtrans_l, uv_gtrans, 2, MPI_REAL, MPI_SUM,    &
    176                               comm2d, ierr )
    177           u_gtrans = uv_gtrans(1) / REAL( numprocs, KIND=wp )
    178           v_gtrans = uv_gtrans(2) / REAL( numprocs, KIND=wp )
     213          CALL MPI_ALLREDUCE( uv_gtrans_l, uv_gtrans, 2, MPI_REAL, MPI_SUM, comm2d, ierr )
     214          u_gtrans = uv_gtrans(1) / REAL( numprocs, KIND = wp )
     215          v_gtrans = uv_gtrans(2) / REAL( numprocs, KIND = wp )
    179216#else
    180217          u_gtrans = uv_gtrans_l(1)
     
    185222
    186223!
    187 !-- Determine the maxima of the velocity components, including their
    188 !-- grid index positions.
    189     CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, u, 'abs', 0.0_wp, &
    190                          u_max, u_max_ijk )
    191     CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, v, 'abs', 0.0_wp, &
    192                          v_max, v_max_ijk )
    193     CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, w, 'abs', 0.0_wp, &
    194                          w_max, w_max_ijk )
     224!-- Determine the maxima of the velocity components, including their grid index positions.
     225    CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, u, 'abs', 0.0_wp, u_max, u_max_ijk )
     226    CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, v, 'abs', 0.0_wp, v_max, v_max_ijk )
     227    CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, w, 'abs', 0.0_wp, w_max, w_max_ijk )
    195228
    196229    IF ( .NOT. dt_fixed )  THEN
     
    215248             DO  j = nys, nyn
    216249                DO  k = nzb+1, nzt
    217                    dt_u_l = MIN( dt_u_l, ( dx     /                               &
    218                                     ( ABS( u(k,j,i) - u_gtrans + u_stokes_zu(k) ) &
    219                                       + 1.0E-10_wp ) ) )
    220                    dt_v_l = MIN( dt_v_l, ( dy     /                               &
    221                                     ( ABS( v(k,j,i) - v_gtrans + v_stokes_zu(k) ) &
    222                                       + 1.0E-10_wp ) ) )
    223                    dt_w_l = MIN( dt_w_l, ( dzu(k) /                               &
    224                                     ( ABS( w(k,j,i) )            + 1.0E-10_wp ) ) )
     250                   dt_u_l = MIN( dt_u_l, ( dx / ( ABS( u(k,j,i) - u_gtrans + u_stokes_zu(k) )      &
     251                                                  + 1.0E-10_wp ) ) )
     252                   dt_v_l = MIN( dt_v_l, ( dy / ( ABS( v(k,j,i) - v_gtrans + v_stokes_zu(k) )      &
     253                                                  + 1.0E-10_wp ) ) )
     254                   dt_w_l = MIN( dt_w_l, ( dzu(k) / ( ABS( w(k,j,i) ) + 1.0E-10_wp ) ) )
    225255                ENDDO
    226256             ENDDO
     
    230260!
    231261!--       Consider the wind speed at the scalar-grid point
    232 !--       !> @note considering the wind speed instead of each individual wind
    233 !--       !>       component is only a workaround so far. This might has to be
    234 !--       !>       changed in the future.
     262!--       !> @note Considering the wind speed instead of each individual wind component is only a
     263!--       !>       workaround so far. This has to be changed in the future.
    235264
    236265          !$ACC PARALLEL LOOP COLLAPSE(3) PRIVATE(i,j,k) &
     
    243272             DO  j = nys, nyn
    244273                DO  k = nzb+1, nzt
    245                    dt_u_l = MIN( dt_u_l, ( MIN( dx, dy, dzu(k) ) / ( &
    246                       SQRT(  ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - u_gtrans + u_stokes_zu(k) )**2   &
    247                            + ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - v_gtrans + v_stokes_zu(k) )**2   &
    248                            + ( 0.5 * ( w(k,j,i) + w(k-1,j,i) )                             )**2 ) &
    249                       + 1.0E-10_wp ) ) )
     274                   dt_u_l = MIN( dt_u_l, ( MIN( dx, dy, dzu(k) ) / ( SQRT(                         &
     275                            ( 0.5 * ( u(k,j,i) + u(k,j,i+1) ) - u_gtrans + u_stokes_zu(k) )**2     &
     276                          + ( 0.5 * ( v(k,j,i) + v(k,j+1,i) ) - v_gtrans + v_stokes_zu(k) )**2     &
     277                          + ( 0.5 * ( w(k,j,i) + w(k-1,j,i) ) )**2 ) + 1.0E-10_wp ) ) )
    250278                ENDDO
    251279             ENDDO
    252280          ENDDO
    253          
     281
    254282          dt_v_l = dt_u_l
    255283          dt_w_l = dt_u_l
     
    274302!
    275303!--    Compute time step according to the diffusion criterion.
    276 !--    First calculate minimum grid spacing which only depends on index k.
    277 !--    When using the dynamic subgrid model, negative km are possible.
     304!--    First calculate minimum grid spacing which only depends on index k. When using the dynamic
     305!--    subgrid model, negative km are possible.
    278306       dt_diff_l = 999999.0_wp
    279307
    280308       !$ACC PARALLEL LOOP PRESENT(dxyz2_min, dzw)
    281309       DO  k = nzb+1, nzt
    282            dxyz2_min(k) = MIN( dx2, dy2, dzw(k)*dzw(k) ) * 0.125_wp
     310           dxyz2_min(k) = MIN( dx2, dy2, dzw(k) * dzw(k) ) * 0.125_wp
    283311       ENDDO
    284312
     
    291319          DO  j = nys, nyn
    292320             DO  k = nzb+1, nzt
    293                 dt_diff_l = MIN( dt_diff_l,                                       &
    294                                  dxyz2_min(k) /                                   &
    295                                     ( MAX( kh(k,j,i), 2.0_wp * ABS( km(k,j,i) ) ) &
    296                                       + 1E-20_wp ) )
     321                dt_diff_l = MIN( dt_diff_l, dxyz2_min(k) / ( MAX( kh(k,j,i), 2.0_wp *              &
     322                            ABS( km(k,j,i) ) ) + 1E-20_wp ) )
    297323             ENDDO
    298324          ENDDO
     
    301327#if defined( __parallel )
    302328       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    303        CALL MPI_ALLREDUCE( dt_diff_l, dt_diff, 1, MPI_REAL, MPI_MIN, comm2d,   &
    304                            ierr )
     329       CALL MPI_ALLREDUCE( dt_diff_l, dt_diff, 1, MPI_REAL, MPI_MIN, comm2d, ierr )
    305330#else
    306331       dt_diff = dt_diff_l
     
    308333
    309334!
    310 !--    The time step is the minimum of the 3-4 components and the diffusion time
    311 !--    step minus a reduction (cfl_factor) to be on the safe side.
     335!--    The time step is the minimum of the 3-4 components and the diffusion time step minus a
     336!--    reduction (cfl_factor) to be on the safe side.
    312337!--    The time step must not exceed the maximum allowed value.
    313338       dt_3d = cfl_factor * MIN( dt_diff, dt_u, dt_v, dt_w, dt_precipitation )
     
    328353
    329354!
    330 !--       Determine the maxima of the diffusion coefficients, including their
    331 !--       grid index positions.
    332           CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, km, 'abs',  &
    333                                0.0_wp, km_max, km_max_ijk )
    334           CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, kh, 'abs',  &
    335                                0.0_wp, kh_max, kh_max_ijk )
    336 
    337           WRITE( message_string, * ) 'Time step has reached minimum limit.',   &
    338                '&dt              = ', dt_3d, ' s  Simulation is terminated.',  &
    339                '&dt_u            = ', dt_u, ' s',                              &
    340                '&dt_v            = ', dt_v, ' s',                              &
    341                '&dt_w            = ', dt_w, ' s',                              &
    342                '&dt_diff         = ', dt_diff, ' s',                           &
    343                '&u_max           = ', u_max, ' m/s    k=', u_max_ijk(1),       &
    344                '  j=', u_max_ijk(2), '  i=', u_max_ijk(3),                     &
    345                '&v_max           = ', v_max, ' m/s    k=', v_max_ijk(1),       &
    346                '  j=', v_max_ijk(2), '  i=', v_max_ijk(3),                     &
    347                '&w_max           = ', w_max, ' m/s    k=', w_max_ijk(1),       &
    348                '  j=', w_max_ijk(2), '  i=', w_max_ijk(3),                     &
    349                '&km_max          = ', km_max, ' m2/s2  k=', km_max_ijk(1),     &
    350                '  j=', km_max_ijk(2), '  i=', km_max_ijk(3),                   &
    351                '&kh_max          = ', kh_max, ' m2/s2  k=', kh_max_ijk(1),     &
     355!--       Determine the maxima of the diffusion coefficients, including their grid index positions.
     356          CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, km, 'abs', 0.0_wp, km_max,      &
     357                               km_max_ijk )
     358          CALL global_min_max( nzb, nzt+1, nysg, nyng, nxlg, nxrg, kh, 'abs', 0.0_wp, kh_max,      &
     359                               kh_max_ijk )
     360
     361          WRITE( message_string, * ) 'Time step has reached minimum limit.',                       &
     362               '&dt              = ', dt_3d, ' s  Simulation is terminated.',                      &
     363               '&dt_u            = ', dt_u, ' s',                                                  &
     364               '&dt_v            = ', dt_v, ' s',                                                  &
     365               '&dt_w            = ', dt_w, ' s',                                                  &
     366               '&dt_diff         = ', dt_diff, ' s',                                               &
     367               '&u_max           = ', u_max, ' m/s    k=', u_max_ijk(1),                           &
     368               '  j=', u_max_ijk(2), '  i=', u_max_ijk(3),                                         &
     369               '&v_max           = ', v_max, ' m/s    k=', v_max_ijk(1),                           &
     370               '  j=', v_max_ijk(2), '  i=', v_max_ijk(3),                                         &
     371               '&w_max           = ', w_max, ' m/s    k=', w_max_ijk(1),                           &
     372               '  j=', w_max_ijk(2), '  i=', w_max_ijk(3),                                         &
     373               '&km_max          = ', km_max, ' m2/s2  k=', km_max_ijk(1),                         &
     374               '  j=', km_max_ijk(2), '  i=', km_max_ijk(3),                                       &
     375               '&kh_max          = ', kh_max, ' m2/s2  k=', kh_max_ijk(1),                         &
    352376                '  j=', kh_max_ijk(2), '  i=', kh_max_ijk(3)
    353377          CALL message( 'timestep', 'PA0312', 0, 1, 0, 6, 0 )
    354378!
    355 !--       In case of coupled runs inform the remote model of the termination
    356 !--       and its reason, provided the remote model has not already been
    357 !--       informed of another termination reason (terminate_coupled > 0) before.
     379!--       In case of coupled runs inform the remote model of the termination and its reason,
     380!--       provided the remote model has not already been informed of another termination reason
     381!--       (terminate_coupled > 0).
    358382#if defined( __parallel )
    359383          IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0 )  THEN
    360384             terminate_coupled = 2
    361385             IF ( myid == 0 )  THEN
    362                 CALL MPI_SENDRECV( &
    363                      terminate_coupled,        1, MPI_INTEGER, target_id,  0,  &
    364                      terminate_coupled_remote, 1, MPI_INTEGER, target_id,  0,  &
    365                      comm_inter, status, ierr )
     386                CALL MPI_SENDRECV( terminate_coupled, 1, MPI_INTEGER, target_id, 0,                &
     387                                   terminate_coupled_remote, 1, MPI_INTEGER, target_id,  0,        &
     388                                   comm_inter, status, ierr )
    366389             ENDIF
    367              CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,      &
    368                              comm2d, ierr)
     390             CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d, ierr)
    369391          ENDIF
    370392#endif
     
    372394
    373395!
    374 !--    In case of nested runs all parent/child processes have to terminate if
    375 !--    one process has set the stop flag, i.e. they need to set the stop flag
    376 !--    too.
     396!--    In case of nested runs all parent/child processes have to terminate if one process has set
     397!--    the stop flag, i.e. they need to set the stop flag too.
    377398       IF ( nested_run )  THEN
    378399          stop_dt_local = stop_dt
    379400#if defined( __parallel )
    380           CALL MPI_ALLREDUCE( stop_dt_local, stop_dt, 1, MPI_LOGICAL, MPI_LOR, &
    381                               MPI_COMM_WORLD, ierr )
     401          CALL MPI_ALLREDUCE( stop_dt_local, stop_dt, 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, ierr )
    382402#endif
    383403       ENDIF
     
    395415#if defined( __parallel )
    396416!
    397 !-- Vertical nesting: coarse and fine grid timestep has to be identical   
     417!-- Vertical nesting: coarse and fine grid timestep has to be identical
    398418    IF ( vnested )  CALL vnest_timestep_sync
    399419#endif
Note: See TracChangeset for help on using the changeset viewer.