source: palm/trunk/SOURCE/check_for_restart.f90 @ 1682

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

  • Property svn:keywords set to Id
File size: 9.8 KB
RevLine 
[1682]1!> @file check_for_restart.f90
[1036]2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
[1310]16! Copyright 1997-2014 Leibniz Universitaet Hannover
[1036]17!--------------------------------------------------------------------------------!
18!
[247]19! Current revisions:
[1]20! -----------------
[1682]21! Code annotations made doxygen readable
[1354]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: check_for_restart.f90 1682 2015-10-07 23:56:08Z knoop $
26!
[1510]27! 1509 2014-12-16 08:56:46Z heinze
28! bugfix: prevent infinite loop in case of automatic restarts
29!
[1469]30! 1468 2014-09-24 14:06:57Z maronga
31! Added support for unscheduled job termination using the flag files
32! DO_STOP_NOW and DO_RESTART_NOW
33!
[1354]34! 1353 2014-04-08 15:21:23Z heinze
35! REAL constants provided with KIND-attribute
36!
[1321]37! 1320 2014-03-20 08:40:49Z raasch
[1320]38! ONLY-attribute added to USE-statements,
39! kind-parameters added to all INTEGER and REAL declaration statements,
40! kinds are defined in new module kinds,
41! revision history before 2012 removed,
42! comment fields (!:) to be used for variable explanations added to
43! all variable declaration statements
[1]44!
[1037]45! 1036 2012-10-22 13:43:42Z raasch
46! code put under GPL (PALM 3.9)
47!
[1033]48! 1032 2012-10-21 13:03:21Z letzel
49! minor reformatting
50!
[1]51! Revision 1.1  1998/03/18 20:06:51  raasch
52! Initial revision
53!
54!
55! Description:
56! ------------
[1682]57!> Set stop flag, if restart is neccessary because of expiring cpu-time or
58!> if it is forced by user
[1]59!------------------------------------------------------------------------------!
[1682]60 SUBROUTINE check_for_restart
61 
[1]62
[1320]63    USE control_parameters,                                                    &
64        ONLY:  coupling_mode, dt_restart, end_time, message_string,            &
65               run_description_header, simulated_time, terminate_coupled,      &
66               terminate_coupled_remote, terminate_run,                        &
67               termination_time_needed, time_restart,                          &
68               time_since_reference_point, write_binary
69    USE kinds
[1]70    USE pegrid
71
72    IMPLICIT NONE
73
74
[1682]75    LOGICAL :: terminate_run_l           !<
76    LOGICAL :: do_stop_now = .FALSE.     !<
77    LOGICAL :: do_restart_now = .FALSE.  !<
[1]78
[1682]79    REAL(wp) ::  remaining_time !<
[1]80
[1320]81
[1]82!
83!-- Check remaining CPU-time
84    CALL local_tremain( remaining_time )
85
86!
87!-- If necessary set a flag to stop the model run
88    terminate_run_l = .FALSE.
[1320]89    IF ( remaining_time <= termination_time_needed  .AND.                      &
[1]90         write_binary(1:4) == 'true' )  THEN
91
92       terminate_run_l = .TRUE.
93    ENDIF
94
95#if defined( __parallel )
96!
97!-- Make a logical OR for all processes. Stop the model run if at least
98!-- one processor has reached the time limit.
[622]99    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
[1320]100    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,        &
[1]101                        MPI_LOR, comm2d, ierr )
102#else
103    terminate_run = terminate_run_l
104#endif
105
106!
107!-- Output that job will be terminated
108    IF ( terminate_run  .AND.  myid == 0 )  THEN
[1320]109       WRITE( message_string, * ) 'run will be terminated because it is ',     &
110                       'running out of job cpu limit & ',                      &
111                       'remaining time:         ', remaining_time, ' s',       &
[274]112                       'termination time needed:', termination_time_needed, ' s'
[247]113       CALL message( 'check_for_restart', 'PA0163', 0, 1, 0, 6, 0 )
[1]114    ENDIF
115
116!
[108]117!-- In case of coupled runs inform the remote model of the termination
118!-- and its reason, provided the remote model has not already been
119!-- informed of another termination reason (terminate_coupled > 0) before,
120!-- or vice versa (terminate_coupled_remote > 0).
[1320]121    IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled'  .AND.       &
[110]122         terminate_coupled == 0  .AND.  terminate_coupled_remote == 0 )  THEN
123
[108]124       terminate_coupled = 3
[1468]125
[222]126#if defined( __parallel )
[667]127       IF ( myid == 0 ) THEN
[1032]128          CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,         &
129                             target_id, 0,                                     &
130                             terminate_coupled_remote, 1, MPI_INTEGER,         &
131                             target_id, 0,                                     &
[667]132                             comm_inter, status, ierr )
133       ENDIF
[1320]134       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0, comm2d,    &
[1032]135                       ierr )
[222]136#endif
[108]137    ENDIF
138
[1468]139
[108]140!
[1468]141!-- Check if a flag file exists that forces a termination of the model
142    IF ( myid == 0 )  THEN
143       INQUIRE(FILE="DO_STOP_NOW", EXIST=do_stop_now)
144       INQUIRE(FILE="DO_RESTART_NOW", EXIST=do_restart_now)
145
146       IF ( do_stop_now .OR. do_restart_now )  THEN
147
148          terminate_run_l = .TRUE.
149
150          WRITE( message_string, * ) 'run will be terminated because user ',   &
151                                  'forced a job finialization using a flag',   &
152                                  'file:',                                     &
153                                  '&DO_STOP_NOW: ', do_stop_now,               &
154                                  '&DO_RESTART_NOW: ', do_restart_now 
155          CALL message( 'check_for_restart', 'PA0398', 0, 0, 0, 6, 0 )
156
157       ENDIF
158    ENDIF
159
160
161#if defined( __parallel )
162!
163!-- Make a logical OR for all processes. Stop the model run if at least
164!-- one processor has reached the time limit.
165    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
166    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,        &
167                        MPI_LOR, comm2d, ierr )
168#else
169    terminate_run = terminate_run_l
170#endif
171
172!
173!-- In case of coupled runs inform the remote model of the termination
174!-- and its reason, provided the remote model has not already been
175!-- informed of another termination reason (terminate_coupled > 0) before,
176!-- or vice versa (terminate_coupled_remote > 0).
177    IF ( terminate_run .AND. coupling_mode /= 'uncoupled' .AND.                &
178         terminate_coupled == 0 .AND.  terminate_coupled_remote == 0 )  THEN
179
180       terminate_coupled = 6
181
182#if defined( __parallel )
183       IF ( myid == 0 ) THEN
184          CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,      &
185                             target_id,  0,                                 &
186                             terminate_coupled_remote, 1, MPI_INTEGER,      &
187                             target_id,  0,                                 &
188                             comm_inter, status, ierr )   
189       ENDIF
190       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,         &
191                       comm2d, ierr ) 
192#endif
193
194    ENDIF
195
196!
197!-- Set the stop flag also, if restart is forced by user settings
198    IF ( time_restart /= 9999999.9_wp  .AND.                                   &
[291]199         time_restart < time_since_reference_point )  THEN
200
[1]201!
202!--    Restart is not neccessary, if the end time of the run (given by
203!--    the user) has been reached
204       IF ( simulated_time < end_time )  THEN
205          terminate_run = .TRUE.
206!
207!--       Increment restart time, if forced by user, otherwise set restart
208!--       time to default (no user restart)
[1353]209          IF ( dt_restart /= 9999999.9_wp )  THEN
[1]210             time_restart = time_restart + dt_restart
211          ELSE
[1353]212             time_restart = 9999999.9_wp
[1]213          ENDIF
214
[1320]215          WRITE( message_string, * ) 'run will be terminated due to user ',    &
216                                  'settings of',                               &
217                                  '&restart_time / dt_restart',                &
[274]218                                  '&new restart time is: ', time_restart, ' s' 
219          CALL message( 'check_for_restart', 'PA0164', 0, 0, 0, 6, 0 )
[247]220 
[108]221!
222!--       In case of coupled runs inform the remote model of the termination
223!--       and its reason, provided the remote model has not already been
224!--       informed of another termination reason (terminate_coupled > 0) before,
225!--       or vice versa (terminate_coupled_remote > 0).
[1320]226          IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0       &
[206]227               .AND.  terminate_coupled_remote == 0 )  THEN
[110]228
[1353]229             IF ( dt_restart /= 9999999.9_wp )  THEN
[108]230                terminate_coupled = 4
231             ELSE
232                terminate_coupled = 5
233             ENDIF
[222]234#if defined( __parallel )
[667]235             IF ( myid == 0 ) THEN
[1032]236                CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,   &
237                                   target_id,  0,                              &
238                                   terminate_coupled_remote, 1, MPI_INTEGER,   &
239                                   target_id,  0,                              &
[667]240                                   comm_inter, status, ierr )   
241             ENDIF
[1320]242             CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,      &
[1032]243                             comm2d, ierr ) 
[222]244#endif
[108]245          ENDIF
246       ELSE
[1353]247          time_restart = 9999999.9_wp
[1]248       ENDIF
249    ENDIF
250
251!
252!-- If the run is stopped, set a flag file which is necessary to initiate
[1468]253!-- the start of a continuation run, except if the user forced to stop the
254!-- run without restart
255    IF ( terminate_run  .AND.  myid == 0 .AND. .NOT. do_stop_now)  THEN
[1]256
257       OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' )
258       WRITE ( 90, '(A)' )  TRIM( run_description_header )
259       CLOSE ( 90 )
260
261    ENDIF
262
263
264 END SUBROUTINE check_for_restart
Note: See TracBrowser for help on using the repository browser.