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

Last change on this file since 1015 was 810, checked in by maronga, 12 years ago

last commit documented

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