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

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

Bugfix: cpp directives .NOT., .AND. replaced by !,&&. Minor bugfixes in mrungui

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