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

Last change on this file since 1 was 1, checked in by raasch, 17 years ago

Initial repository layout and content

File size: 4.2 KB
Line 
1 SUBROUTINE check_for_restart
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! -----------------
10! $Log: check_for_restart.f90,v $
11! Revision 1.11  2007/02/11 12:55:13  raasch
12! Informative output to the job protocol
13!
14! Revision 1.10  2003/03/16 09:27:49  raasch
15! Two underscores (_) are placed in front of all define-strings
16!
17! Revision 1.9  2002/12/19 13:48:59  raasch
18! Stop flag is also set in case of user forced restarts, routine name
19! changed from check_cpu_time to check_for_restart, the run description
20! header will be written on file CONTINUE_RUN
21!
22! Revision 1.8  2001/08/21 08:22:23  raasch
23! MPI_ALLREDUCE moved out of IF-clause
24!
25! Revision 1.7  2001/03/30 06:56:28  raasch
26! Translation of remaining German identifiers (variables, subroutines, etc.)
27!
28! Revision 1.6  2001/01/22 05:36:33  raasch
29! Module test_variables removed
30!
31! Revision 1.5  2001/01/02 17:19:27  raasch
32! Initial value of terminate_run_l is set to .FALSE. (undefined before).
33! Flag file will only be created by PE0. Unit 90 is used instead of 91.
34!
35! Revision 1.4  2000/01/21 16:27:59  letzel
36! All comments translated into English
37!
38! Revision 1.3  1998/07/06 12:07:47  raasch
39! + USE test_variables
40!
41! Revision 1.2  1998/03/24 15:24:54  raasch
42! Lauf wird nur dann beendet und Fortsetzungslauf gestartet, falls auch eine
43! Abspeicherung der entsprechenden Binaerdateien vorgesehen ist.
44! Beendigung der Rechnung auf mehreren Prozessoren richtig implementiert.
45!
46! Revision 1.1  1998/03/18 20:06:51  raasch
47! Initial revision
48!
49!
50! Description:
51! ------------
52! Set stop flag, if restart is neccessary because of expiring cpu-time or
53! if it is forced by user
54!------------------------------------------------------------------------------!
55
56    USE pegrid
57    USE control_parameters
58
59    IMPLICIT NONE
60
61
62    LOGICAL :: terminate_run_l
63    REAL ::  remaining_time
64
65
66!
67!-- Check remaining CPU-time
68    CALL local_tremain( remaining_time )
69
70!
71!-- If necessary set a flag to stop the model run
72    terminate_run_l = .FALSE.
73    IF ( remaining_time <= termination_time_needed  .AND. &
74         write_binary(1:4) == 'true' )  THEN
75
76       terminate_run_l = .TRUE.
77    ENDIF
78
79#if defined( __parallel )
80!
81!-- Make a logical OR for all processes. Stop the model run if at least
82!-- one processor has reached the time limit.
83    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL, &
84                        MPI_LOR, comm2d, ierr )
85#else
86    terminate_run = terminate_run_l
87#endif
88
89!
90!-- Output that job will be terminated
91    IF ( terminate_run  .AND.  myid == 0 )  THEN
92       PRINT*, '*** WARNING: run will be terminated because it is running out of job cpu', &
93                    'limit'
94       PRINT*, '             remaining time:         ', remaining_time, ' s'
95       PRINT*, '             termination time needed:', termination_time_needed, ' s'
96    ENDIF
97
98!
99!-- Set the stop flag also, if restart is forced by user
100    IF ( time_restart /= 9999999.9  .AND.  time_restart < simulated_time ) &
101    THEN
102!
103!--    Restart is not neccessary, if the end time of the run (given by
104!--    the user) has been reached
105       IF ( simulated_time < end_time )  THEN
106          terminate_run = .TRUE.
107!
108!--       Increment restart time, if forced by user, otherwise set restart
109!--       time to default (no user restart)
110          IF ( dt_restart /= 9999999.9 )  THEN
111             time_restart = time_restart + dt_restart
112          ELSE
113             time_restart = 9999999.9
114          ENDIF
115
116          IF ( myid == 0 )  THEN
117             PRINT*, '*** INFORMATIVE: run will be terminated due to user settings of'
118             PRINT*, '                 restart_time / dt_restart'
119             PRINT*, '                 new restart time is: ', time_restart, ' s'
120          ENDIF
121    ELSE
122          time_restart = 9999999.9
123       ENDIF
124    ENDIF
125
126!
127!-- If the run is stopped, set a flag file which is necessary to initiate
128!-- the start of a continuation run
129    IF ( terminate_run  .AND.  myid == 0 )  THEN
130
131       OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' )
132       WRITE ( 90, '(A)' )  TRIM( run_description_header )
133       CLOSE ( 90 )
134
135    ENDIF
136
137
138 END SUBROUTINE check_for_restart
Note: See TracBrowser for help on using the repository browser.