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

Last change on this file since 213 was 213, checked in by raasch, 15 years ago

Output message can be handled with new subroutine handle_palm_message. All output messages will be replaced by this routine step by step within the next revisions

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