Ignore:
Timestamp:
Sep 14, 2020 7:55:28 AM (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/local_stop.f90

    r4564 r4677  
    11!> @file local_stop.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    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! 4564 2020-06-12 14:03:36Z raasch
    2729! Vertical nesting method of Huq et al. (2019) removed
    28 ! 
     30!
    2931! 4444 2020-03-05 15:59:50Z raasch
    3032! bugfix: misplaced cpp-directive moved
    31 ! 
     33!
    3234! 4360 2020-01-07 11:25:50Z suehring
    3335! Corrected "Former revisions" section
    34 ! 
     36!
    3537! 3655 2019-01-07 16:51:22Z knoop
    3638! Added an empty output string to stop keywords to clean up job protocol
     
    4345! ------------
    4446!> Stop program execution
    45 !------------------------------------------------------------------------------!
     47!--------------------------------------------------------------------------------------------------!
    4648 SUBROUTINE local_stop
    47  
     49
    4850#if defined( __parallel )
    4951
    50     USE control_parameters,                                                    &
    51         ONLY:  abort_mode, coupling_mode, coupling_mode_remote, dt_restart,    &
    52                stop_dt, terminate_coupled, terminate_coupled_remote,           &
    53                terminate_run, time_restart
     52    USE control_parameters,                                                                        &
     53        ONLY:  abort_mode, coupling_mode, coupling_mode_remote, dt_restart, stop_dt,               &
     54               terminate_coupled, terminate_coupled_remote, terminate_run, time_restart
    5455
    5556    USE pegrid
    5657
    57     USE pmc_interface,                                                         &
     58    USE pmc_interface,                                                                             &
    5859        ONLY:  nested_run
    5960
     
    6364       IF ( nested_run )  THEN
    6465!
    65 !--       Workaround: If any of the nested model crashes, it aborts the whole
    66 !--       run with MPI_ABORT, regardless of the reason given by abort_mode
     66!--       Workaround: If any of the nested model crashes, it aborts the whole run with MPI_ABORT,
     67!--                   regardless of the reason given by abort_mode
    6768          CALL MPI_ABORT( MPI_COMM_WORLD, 9999, ierr )
    6869       ELSE
     
    8485             IF ( myid == 0 )  THEN
    8586                PRINT*, '+++ local_stop:'
    86                 PRINT*, '    local model "', TRIM( coupling_mode ), &
    87                      '" stops now'
     87                PRINT*, '    local model "', TRIM( coupling_mode ), '" stops now'
    8888             ENDIF
    8989!
    90 !--          Inform the remote model of the termination and its reason, provided
    91 !--          the remote model has not already been informed of another
    92 !--          termination reason (terminate_coupled > 0) before.
     90!--          Inform the remote model of the termination and its reason, provided the remote model
     91!--          has not already been informed of another termination reason (terminate_coupled > 0)
     92!--          before.
    9393             IF ( terminate_coupled == 0 )  THEN
    9494                terminate_coupled = 1
    9595                IF ( myid == 0 ) THEN
    96                    CALL MPI_SENDRECV( &
    97                         terminate_coupled,        1, MPI_INTEGER, target_id,  0, &
    98                         terminate_coupled_remote, 1, MPI_INTEGER, target_id,  0, &
     96                   CALL MPI_SENDRECV(                                                              &
     97                        terminate_coupled,        1, MPI_INTEGER, target_id,  0,                   &
     98                        terminate_coupled_remote, 1, MPI_INTEGER, target_id,  0,                   &
    9999                        comm_inter, status, ierr )
    100100                ENDIF
     
    107107             IF ( myid == 0 )  THEN
    108108                PRINT*, '+++ local_stop:'
    109                 PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
    110                      '" stopped'
     109                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" stopped'
    111110             ENDIF
    112111             CALL MPI_FINALIZE( ierr )
     
    116115             IF ( myid == 0 )  THEN
    117116                PRINT*, '+++ local_stop:'
    118                 PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
    119                      '" terminated'
     117                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
    120118                PRINT*, '    with stop_dt = .T.'
    121119             ENDIF
     
    125123             IF ( myid == 0 )  THEN
    126124                PRINT*, '+++ local_stop:'
    127                 PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
    128                      '" terminated'
     125                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
    129126                PRINT*, '    with terminate_run = .T. (CPU-time limit)'
    130127             ENDIF
     
    134131             IF ( myid == 0 )  THEN
    135132                PRINT*, '+++ local_stop:'
    136                 PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
    137                      '" terminated'
     133                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
    138134                PRINT*, '    with terminate_run = .T. (restart)'
    139135             ENDIF
     
    144140             IF ( myid == 0 )  THEN
    145141                PRINT*, '+++ local_stop:'
    146                 PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
    147                      '" terminated'
     142                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
    148143                PRINT*, '    with terminate_run = .T. (single restart)'
    149144             ENDIF
     
    161156#endif
    162157
    163  END SUBROUTINE local_stop   
     158 END SUBROUTINE local_stop
Note: See TracChangeset for help on using the changeset viewer.