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

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

new utility check_namelist_files implemented

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