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

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

further updates for turbulent inflow: reading input data of a precursor run using a smaller total domain is working

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