source: palm/tags/release-3.8/SOURCE/local_stop.f90 @ 716

Last change on this file since 716 was 668, checked in by suehring, 13 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 4.2 KB
Line 
1 SUBROUTINE local_stop
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7! Former revisions:
8! -----------------
9! $Id: local_stop.f90 668 2010-12-23 13:22:58Z raasch $
10!
11! 667 2010-12-23 12:06:00Z suehring/gryschka
12! Exchange of terminate_coupled between ocean and atmosphere via PE0
13!
14! 213 2008-11-13 10:26:18Z raasch
15! Implementation of a MPI-1 coupling: replaced myid with target_id.
16! The uncoupled case allows stop or mpi_abort depending on new steering
17! parameter abort_mode, which is set in routine message.
18!
19! 147 2008-02-01 12:41:46Z raasch
20! Bugfix: a stop command was missing in some cases of the parallel branch
21!
22! 108 2007-08-24 15:10:38Z letzel
23! modifications to terminate coupled runs
24!
25! RCS Log replace by Id keyword, revision history cleaned up
26!
27! Revision 1.2  2003/03/16 09:40:28  raasch
28! Two underscores (_) are placed in front of all define-strings
29!
30! Revision 1.1  2002/12/19 15:46:23  raasch
31! Initial revision
32!
33!
34! Description:
35! ------------
36! Stop program execution
37!------------------------------------------------------------------------------!
38
39    USE pegrid
40    USE control_parameters
41
42
43#if defined( __parallel )
44    IF ( coupling_mode == 'uncoupled' )  THEN
45       IF ( abort_mode == 1 )  THEN
46          CALL MPI_FINALIZE( ierr )
47          STOP
48       ELSEIF ( abort_mode == 2 )  THEN
49          CALL MPI_ABORT( comm2d, 9999, ierr )
50       ENDIF
51    ELSE
52
53       SELECT CASE ( terminate_coupled_remote )
54
55          CASE ( 0 )
56             IF ( myid == 0 )  THEN
57                PRINT*, '+++ local_stop:'
58                PRINT*, '    local model "', TRIM( coupling_mode ), &
59                     '" stops now'
60             ENDIF
61!
62!--          Inform the remote model of the termination and its reason, provided
63!--          the remote model has not already been informed of another
64!--          termination reason (terminate_coupled > 0) before.
65             IF ( terminate_coupled == 0 )  THEN
66                terminate_coupled = 1
67                IF ( myid == 0 ) THEN
68                   CALL MPI_SENDRECV( &
69                        terminate_coupled,        1, MPI_INTEGER, target_id,  0, &
70                        terminate_coupled_remote, 1, MPI_INTEGER, target_id,  0, &
71                        comm_inter, status, ierr )
72                ENDIF
73                CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_REAL, 0, comm2d, ierr)
74             ENDIF
75             CALL MPI_FINALIZE( ierr )
76             STOP
77
78          CASE ( 1 )
79             IF ( myid == 0 )  THEN
80                PRINT*, '+++ local_stop:'
81                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
82                     '" stopped'
83             ENDIF
84             CALL MPI_FINALIZE( ierr )
85             STOP
86
87          CASE ( 2 )
88             IF ( myid == 0 )  THEN
89                PRINT*, '+++ local_stop:'
90                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
91                     '" terminated'
92                PRINT*, '    with stop_dt = .T.'
93             ENDIF
94             stop_dt = .TRUE.
95
96          CASE ( 3 )
97             IF ( myid == 0 )  THEN
98                PRINT*, '+++ local_stop:'
99                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
100                     '" terminated'
101                PRINT*, '    with terminate_run = .T. (CPU-time limit)'
102             ENDIF
103             terminate_run = .TRUE.
104
105          CASE ( 4 )
106             IF ( myid == 0 )  THEN
107                PRINT*, '+++ local_stop:'
108                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
109                     '" terminated'
110                PRINT*, '    with terminate_run = .T. (restart)'
111             ENDIF
112             terminate_run = .TRUE.
113             time_restart = time_restart + dt_restart
114
115          CASE ( 5 )
116             IF ( myid == 0 )  THEN
117                PRINT*, '+++ local_stop:'
118                PRINT*, '    remote model "', TRIM( coupling_mode_remote ), &
119                     '" terminated'
120                PRINT*, '    with terminate_run = .T. (single restart)'
121             ENDIF
122             terminate_run = .TRUE.
123             time_restart = 9999999.9
124
125       END SELECT
126
127    ENDIF
128
129#else
130
131    STOP
132
133#endif
134
135 END SUBROUTINE local_stop   
Note: See TracBrowser for help on using the repository browser.