Ignore:
Timestamp:
May 19, 2020 3:45:12 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard, redundant if statement removed

File:
1 edited

Legend:

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

    r4360 r4542  
    11!> @file check_for_restart.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! 4360 2020-01-07 11:25:50Z suehring
    2729! Corrected "Former revisions" section
    28 ! 
     30!
    2931! 3655 2019-01-07 16:51:22Z knoop
    3032! Error messages revised
     
    3638! Description:
    3739! ------------
    38 !> Set stop flag, if restart is neccessary because of expiring cpu-time or
    39 !> if it is forced by user
    40 !------------------------------------------------------------------------------!
     40!> Set stop flag, if restart is neccessary because of expiring cpu-time or if it is forced by user.
     41!--------------------------------------------------------------------------------------------------!
    4142 SUBROUTINE check_for_restart
    42  
    43 
    44     USE control_parameters,                                                    &
    45         ONLY:  coupling_mode, dt_restart, end_time, message_string,            &
    46                run_description_header, simulated_time, terminate_coupled,      &
    47                terminate_coupled_remote, terminate_run,                        &
    48                termination_time_needed, time_restart,                          &
    49                time_since_reference_point, write_binary
     43
     44
     45    USE control_parameters,                                                                        &
     46        ONLY:  coupling_mode, dt_restart, end_time, message_string, run_description_header,        &
     47               simulated_time, terminate_coupled, terminate_coupled_remote, terminate_run,         &
     48               termination_time_needed, time_restart, time_since_reference_point, write_binary
    5049
    5150    USE kinds
     
    5352    USE pegrid
    5453
    55     USE pmc_interface,                                                         &
     54    USE pmc_interface,                                                                             &
    5655        ONLY:  comm_world_nesting, cpl_id, nested_run
    5756
     
    8079
    8180!
    82 !-- Set the global communicator to be used (depends on the mode in which PALM is
    83 !-- running)
     81!-- Set the global communicator to be used (depends on the mode in which PALM is running)
    8482    IF ( nested_run )  THEN
    8583       global_communicator = comm_world_nesting
     
    9088#if defined( __parallel )
    9189!
    92 !-- Make a logical OR for all processes. Stop the model run if at least
    93 !-- one process has reached the time limit.
     90!-- Make a logical OR for all processes. Stop the model run if at least one process has reached the
     91!-- time limit.
    9492    IF ( collective_wait )  CALL MPI_BARRIER( global_communicator, ierr )
    95     CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,     &
    96                         MPI_LOR, global_communicator, ierr )
     93    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL, MPI_LOR,                   &
     94                        global_communicator, ierr )
    9795#else
    9896    terminate_run = terminate_run_l
     
    102100!-- Output that job will be terminated
    103101    IF ( terminate_run  .AND.  myid == 0 )  THEN
    104        WRITE( message_string, * ) 'run will be terminated because it is ',     &
    105                        'running out of job cpu limit & ',                      &
    106                        'remaining time:         ', remaining_time, ' s &',     &
    107                        'termination time needed:', termination_time_needed, ' s'
     102       WRITE( message_string, * ) 'run will be terminated because it is ',                         &
     103                                  'running out of job cpu limit & ',                               &
     104                                  'remaining time:         ', remaining_time, ' s &',              &
     105                                  'termination time needed:', termination_time_needed, ' s'
    108106       CALL message( 'check_for_restart', 'PA0163', 0, 1, 0, 6, 0 )
    109107    ENDIF
    110108
    111109!
    112 !-- In case of coupled runs inform the remote model of the termination
    113 !-- and its reason, provided the remote model has not already been
    114 !-- informed of another termination reason (terminate_coupled > 0) before,
    115 !-- or vice versa (terminate_coupled_remote > 0).
    116     IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled'  .AND.       &
     110!-- In case of coupled runs inform the remote model of the termination and its reason, provided the
     111!-- remote model has not already been informed of another termination reason (terminate_coupled > 0)
     112!-- before, or vice versa (terminate_coupled_remote > 0).
     113    IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled'  .AND.                           &
    117114         terminate_coupled == 0  .AND.  terminate_coupled_remote == 0 )  THEN
    118115
     
    121118#if defined( __parallel )
    122119       IF ( myid == 0 ) THEN
    123           CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,         &
    124                              target_id, 0,                                     &
    125                              terminate_coupled_remote, 1, MPI_INTEGER,         &
    126                              target_id, 0,                                     &
     120          CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,                             &
     121                             target_id, 0,                                                         &
     122                             terminate_coupled_remote, 1, MPI_INTEGER,                             &
     123                             target_id, 0,                                                         &
    127124                             comm_inter, status, ierr )
    128125       ENDIF
    129        CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d,    &
    130                        ierr )
    131 #endif
    132     ENDIF
    133 
    134 
    135 !
    136 !-- Check if a flag file exists that forces a termination of the model
     126       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d, ierr )
     127#endif
     128    ENDIF
     129
     130
     131!
     132!-- Check if a flag file exists that forces a termination of the model.
    137133    IF ( myid == 0 )  THEN
    138134       INQUIRE(FILE="DO_STOP_NOW", EXIST=do_stop_now)
     
    143139          terminate_run_l = .TRUE.
    144140
    145           WRITE( message_string, * ) 'run will be terminated because user ',   &
    146                                   'forced a job finalization using a flag',    &
    147                                   'file:',                                     &
    148                                   '&DO_STOP_NOW: ', do_stop_now,               &
    149                                   '&DO_RESTART_NOW: ', do_restart_now
     141          WRITE( message_string, * ) 'run will be terminated because user ',                       &
     142                                     'forced a job finalization using a flag',                     &
     143                                     'file:',                                                      &
     144                                     '&DO_STOP_NOW: ', do_stop_now,                                &
     145                                     '&DO_RESTART_NOW: ', do_restart_now
    150146          CALL message( 'check_for_restart', 'PA0398', 0, 0, 0, 6, 0 )
    151147
     
    156152#if defined( __parallel )
    157153!
    158 !-- Make a logical OR for all processes. Stop the model run if a flag file has
    159 !-- been detected above.
     154!-- Make a logical OR for all processes. Stop the model run if a flag file has been detected above.
    160155    IF ( collective_wait )  CALL MPI_BARRIER( global_communicator, ierr )
    161     CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,        &
    162                         MPI_LOR, global_communicator, ierr )
     156    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL, MPI_LOR,                   &
     157                        global_communicator, ierr )
    163158#else
    164159    terminate_run = terminate_run_l
     
    166161
    167162!
    168 !-- In case of coupled runs inform the remote model of the termination
    169 !-- and its reason, provided the remote model has not already been
    170 !-- informed of another termination reason (terminate_coupled > 0) before,
    171 !-- or vice versa (terminate_coupled_remote > 0).
    172     IF ( terminate_run .AND. coupling_mode /= 'uncoupled' .AND.                &
     163!-- In case of coupled runs inform the remote model of the termination and its reason, provided the
     164!-- remote model has not already been informed of another termination reason (terminate_coupled > 0)
     165!-- before, or vice versa (terminate_coupled_remote > 0).
     166    IF ( terminate_run .AND. coupling_mode /= 'uncoupled' .AND.                                    &
    173167         terminate_coupled == 0 .AND.  terminate_coupled_remote == 0 )  THEN
    174168
     
    177171#if defined( __parallel )
    178172       IF ( myid == 0 ) THEN
    179           CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,      &
    180                              target_id,  0,                                 &
    181                              terminate_coupled_remote, 1, MPI_INTEGER,      &
    182                              target_id,  0,                                 &
    183                              comm_inter, status, ierr )   
    184        ENDIF
    185        CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,         &
    186                        comm2d, ierr ) 
     173          CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,                             &
     174                             target_id,  0,                                                        &
     175                             terminate_coupled_remote, 1, MPI_INTEGER,                             &
     176                             target_id,  0,                                                        &
     177                             comm_inter, status, ierr )
     178       ENDIF
     179       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d, ierr )
    187180#endif
    188181
     
    191184!
    192185!-- Set the stop flag also, if restart is forced by user settings
    193     IF ( time_restart /= 9999999.9_wp  .AND.                                   &
    194          time_restart < time_since_reference_point )  THEN
    195 
    196 !
    197 !--    Restart is not neccessary, if the end time of the run (given by
    198 !--    the user) has been reached
     186    IF ( time_restart /= 9999999.9_wp  .AND.  time_restart < time_since_reference_point )  THEN
     187
     188!
     189!--    Restart is not neccessary, if the end time of the run (given by the user) has been reached.
    199190       IF ( simulated_time < end_time )  THEN
    200191          terminate_run = .TRUE.
    201192!
    202 !--       Increment restart time, if forced by user, otherwise set restart
    203 !--       time to default (no user restart)
     193!--       Increment restart time, if forced by user, otherwise set restart time to default (no user
     194!--       restart).
    204195          IF ( dt_restart /= 9999999.9_wp )  THEN
    205196             time_restart = time_restart + dt_restart
     
    208199          ENDIF
    209200
    210           WRITE( message_string, * ) 'run will be terminated due to user ',    &
    211                                   'settings of ',                              &
    212                                   'restart_time / dt_restart, ',               &
    213                                   'new restart time is: ', time_restart, ' s'
     201          WRITE( message_string, * ) 'run will be terminated due to user ',                        &
     202                                     'settings of ',                                               &
     203                                     'restart_time / dt_restart, ',                                &
     204                                     'new restart time is: ', time_restart, ' s'
    214205          CALL message( 'check_for_restart', 'PA0164', 0, 0, 0, 6, 0 )
    215  
    216 !
    217 !--       In case of coupled runs inform the remote model of the termination
    218 !--       and its reason, provided the remote model has not already been
    219 !--       informed of another termination reason (terminate_coupled > 0) before,
    220 !--       or vice versa (terminate_coupled_remote > 0).
    221           IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0       &
     206
     207!
     208!--       In case of coupled runs inform the remote model of the termination and its reason,
     209!--       provided the remote model has not already been informed of another termination reason
     210!--       (terminate_coupled > 0) before, or vice versa (terminate_coupled_remote > 0).
     211          IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0                           &
    222212               .AND.  terminate_coupled_remote == 0 )  THEN
    223213
     
    229219#if defined( __parallel )
    230220             IF ( myid == 0 ) THEN
    231                 CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,   &
    232                                    target_id,  0,                              &
    233                                    terminate_coupled_remote, 1, MPI_INTEGER,   &
    234                                    target_id,  0,                              &
    235                                    comm_inter, status, ierr )   
     221                CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,                       &
     222                                   target_id,  0,                                                  &
     223                                   terminate_coupled_remote, 1, MPI_INTEGER,                       &
     224                                   target_id,  0,                                                  &
     225                                   comm_inter, status, ierr )
    236226             ENDIF
    237              CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,      &
    238                              comm2d, ierr ) 
     227             CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d, ierr )
    239228#endif
    240229          ENDIF
     
    245234
    246235!
    247 !-- If the run is stopped, set a flag file which is necessary to initiate
    248 !-- the start of a continuation run, except if the user forced to stop the
    249 !-- run without restart
    250     IF ( terminate_run  .AND.  myid == 0  .AND.  cpl_id == 1  .AND.            &
    251          .NOT. do_stop_now)  THEN
     236!-- If the run is stopped, set a flag file which is necessary to initiate the start of a
     237!-- continuation run, except if the user forced to stop the run without restart.
     238    IF ( terminate_run  .AND.  myid == 0  .AND.  cpl_id == 1  .AND.  .NOT. do_stop_now)  THEN
    252239
    253240       OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' )
Note: See TracChangeset for help on using the changeset viewer.