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

Last change on this file since 206 was 206, checked in by raasch, 16 years ago

ocean-atmosphere coupling realized with MPI-1, adjustments in mrun, mbuild, subjob for lcxt4

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