source: palm/trunk/SOURCE/local_stop.f90 @ 4901

Last change on this file since 4901 was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

  • Property svn:keywords set to Id
File size: 5.5 KB
RevLine 
[1682]1!> @file local_stop.f90
[4677]2!--------------------------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[4677]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.
[1036]8!
[4677]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.
[1036]12!
[4677]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/>.
[1036]15!
[4828]16! Copyright 1997-2021 Leibniz Universitaet Hannover
[4677]17!--------------------------------------------------------------------------------------------------!
[1036]18!
[484]19! Current revisions:
[1]20! -----------------
[4677]21!
22!
[1]23! Former revisions:
24! -----------------
[3]25! $Id: local_stop.f90 4828 2021-01-05 11:21:41Z banzhafs $
[4677]26! file re-formatted to follow the PALM coding standard
27!
28! 4564 2020-06-12 14:03:36Z raasch
[4564]29! Vertical nesting method of Huq et al. (2019) removed
[4677]30!
[4564]31! 4444 2020-03-05 15:59:50Z raasch
[4444]32! bugfix: misplaced cpp-directive moved
[4677]33!
[4444]34! 4360 2020-01-07 11:25:50Z suehring
[4182]35! Corrected "Former revisions" section
[4677]36!
[4182]37! 3655 2019-01-07 16:51:22Z knoop
[3250]38! Added an empty output string to stop keywords to clean up job protocol
[2716]39!
[4182]40! Revision 1.1  2002/12/19 15:46:23  raasch
41! Initial revision
42!
43!
[1]44! Description:
45! ------------
[1682]46!> Stop program execution
[4677]47!--------------------------------------------------------------------------------------------------!
[1682]48 SUBROUTINE local_stop
[4677]49
[4444]50#if defined( __parallel )
[1]51
[4677]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
[1]55
[1764]56    USE pegrid
[206]57
[4677]58    USE pmc_interface,                                                                             &
[1764]59        ONLY:  nested_run
60
[2365]61
[108]62    IF ( coupling_mode == 'uncoupled' )  THEN
[4564]63
[1764]64       IF ( nested_run )  THEN
65!
[4677]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
[1764]68          CALL MPI_ABORT( MPI_COMM_WORLD, 9999, ierr )
69       ELSE
70          IF ( abort_mode == 1 )  THEN
71             CALL MPI_FINALIZE( ierr )
[3312]72             STOP 1
[1764]73          ELSEIF ( abort_mode == 2 )  THEN
74             CALL MPI_ABORT( comm2d, 9999, ierr )
75          ELSEIF ( abort_mode == 3 )  THEN
76             CALL MPI_ABORT( MPI_COMM_WORLD, 9999, ierr )
77          ENDIF
[213]78       ENDIF
[2365]79
[108]80    ELSE
[1]81
[108]82       SELECT CASE ( terminate_coupled_remote )
83
84          CASE ( 0 )
85             IF ( myid == 0 )  THEN
86                PRINT*, '+++ local_stop:'
[4677]87                PRINT*, '    local model "', TRIM( coupling_mode ), '" stops now'
[108]88             ENDIF
89!
[4677]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.
[108]93             IF ( terminate_coupled == 0 )  THEN
94                terminate_coupled = 1
[667]95                IF ( myid == 0 ) THEN
[4677]96                   CALL MPI_SENDRECV(                                                              &
97                        terminate_coupled,        1, MPI_INTEGER, target_id,  0,                   &
98                        terminate_coupled_remote, 1, MPI_INTEGER, target_id,  0,                   &
[667]99                        comm_inter, status, ierr )
100                ENDIF
101                CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_REAL, 0, comm2d, ierr)
[108]102             ENDIF
103             CALL MPI_FINALIZE( ierr )
[3312]104             STOP 1
[108]105
106          CASE ( 1 )
107             IF ( myid == 0 )  THEN
108                PRINT*, '+++ local_stop:'
[4677]109                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" stopped'
[108]110             ENDIF
111             CALL MPI_FINALIZE( ierr )
[3312]112             STOP 1
[108]113
114          CASE ( 2 )
115             IF ( myid == 0 )  THEN
116                PRINT*, '+++ local_stop:'
[4677]117                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
[108]118                PRINT*, '    with stop_dt = .T.'
119             ENDIF
120             stop_dt = .TRUE.
121
122          CASE ( 3 )
123             IF ( myid == 0 )  THEN
124                PRINT*, '+++ local_stop:'
[4677]125                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
[108]126                PRINT*, '    with terminate_run = .T. (CPU-time limit)'
127             ENDIF
128             terminate_run = .TRUE.
129
130          CASE ( 4 )
131             IF ( myid == 0 )  THEN
132                PRINT*, '+++ local_stop:'
[4677]133                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
[108]134                PRINT*, '    with terminate_run = .T. (restart)'
135             ENDIF
136             terminate_run = .TRUE.
137             time_restart = time_restart + dt_restart
138
139          CASE ( 5 )
140             IF ( myid == 0 )  THEN
141                PRINT*, '+++ local_stop:'
[4677]142                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), '" terminated'
[108]143                PRINT*, '    with terminate_run = .T. (single restart)'
144             ENDIF
145             terminate_run = .TRUE.
[1353]146             time_restart = 9999999.9_wp
[108]147
148       END SELECT
149
150    ENDIF
151
152#else
153
[3312]154    STOP 1
[1]155
[108]156#endif
157
[4677]158 END SUBROUTINE local_stop
Note: See TracBrowser for help on using the repository browser.