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

Last change on this file since 622 was 622, checked in by raasch, 13 years ago

New:
---

Optional barriers included in order to speed up collective operations
MPI_ALLTOALL and MPI_ALLREDUCE. This feature is controlled with new initial
parameter collective_wait. Default is .FALSE, but .TRUE. on SGI-type
systems. (advec_particles, advec_s_bc, buoyancy, check_for_restart,
cpu_statistics, data_output_2d, data_output_ptseries, flow_statistics,
global_min_max, inflow_turbulence, init_3d_model, init_particles, init_pegrid,
init_slope, parin, pres, poismg, set_particle_attributes, timestep,
read_var_list, user_statistics, write_compressed, write_var_list)

Adjustments for Kyushu Univ. (lcrte, ibmku). Concerning hybrid
(MPI/openMP) runs, the number of openMP threads per MPI tasks can now
be given as an argument to mrun-option -O. (mbuild, mrun, subjob)

Changed:


Initialization of the module command changed for SGI-ICE/lcsgi (mbuild, subjob)

Errors:


  • Property svn:keywords set to Id
File size: 5.5 KB
Line 
1 SUBROUTINE check_for_restart
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6! optional barriers included in order to speed up collective operations
7!
8! Former revisions:
9! -----------------
10! $Id: check_for_restart.f90 622 2010-12-10 08:08:13Z raasch $
11!
12! 291 2009-04-16 12:07:26Z raasch
13! Coupling with independent precursor runs.
14! Output of messages replaced by message handling routine
15!
16! 222 2009-01-12 16:04:16Z letzel
17! Implementation of an MPI-1 coupling: replaced myid with target_id
18! Bugfix for nonparallel execution
19!
20! 108 2007-08-24 15:10:38Z letzel
21! modifications to terminate coupled runs
22!
23! RCS Log replace by Id keyword, revision history cleaned up
24!
25! Revision 1.11  2007/02/11 12:55:13  raasch
26! Informative output to the job protocol
27!
28! Revision 1.1  1998/03/18 20:06:51  raasch
29! Initial revision
30!
31!
32! Description:
33! ------------
34! Set stop flag, if restart is neccessary because of expiring cpu-time or
35! if it is forced by user
36!------------------------------------------------------------------------------!
37
38    USE pegrid
39    USE control_parameters
40
41    IMPLICIT NONE
42
43
44    LOGICAL :: terminate_run_l
45    REAL ::  remaining_time
46
47
48!
49!-- Check remaining CPU-time
50    CALL local_tremain( remaining_time )
51
52!
53!-- If necessary set a flag to stop the model run
54    terminate_run_l = .FALSE.
55    IF ( remaining_time <= termination_time_needed  .AND. &
56         write_binary(1:4) == 'true' )  THEN
57
58       terminate_run_l = .TRUE.
59    ENDIF
60
61#if defined( __parallel )
62!
63!-- Make a logical OR for all processes. Stop the model run if at least
64!-- one processor has reached the time limit.
65    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
66    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL, &
67                        MPI_LOR, comm2d, ierr )
68#else
69    terminate_run = terminate_run_l
70#endif
71
72!
73!-- Output that job will be terminated
74    IF ( terminate_run  .AND.  myid == 0 )  THEN
75       WRITE( message_string, * ) 'run will be terminated because it is ', &
76                       'running out of job cpu limit & ',                  &
77                       'remaining time:         ', remaining_time, ' s',   &
78                       'termination time needed:', termination_time_needed, ' s'
79       CALL message( 'check_for_restart', 'PA0163', 0, 1, 0, 6, 0 )
80    ENDIF
81
82!
83!-- In case of coupled runs inform the remote model of the termination
84!-- and its reason, provided the remote model has not already been
85!-- informed of another termination reason (terminate_coupled > 0) before,
86!-- or vice versa (terminate_coupled_remote > 0).
87    IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled'  .AND. &
88         terminate_coupled == 0  .AND.  terminate_coupled_remote == 0 )  THEN
89
90       terminate_coupled = 3
91#if defined( __parallel )
92       CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,          &
93                          target_id, 0,                                      &
94                          terminate_coupled_remote, 1, MPI_INTEGER,          &
95                          target_id, 0,                                      &
96                          comm_inter, status, ierr )
97#endif
98    ENDIF
99
100!
101!-- Set the stop flag also, if restart is forced by user
102    IF ( time_restart /= 9999999.9  .AND.  &
103         time_restart < time_since_reference_point )  THEN
104
105!
106!--    Restart is not neccessary, if the end time of the run (given by
107!--    the user) has been reached
108       IF ( simulated_time < end_time )  THEN
109          terminate_run = .TRUE.
110!
111!--       Increment restart time, if forced by user, otherwise set restart
112!--       time to default (no user restart)
113          IF ( dt_restart /= 9999999.9 )  THEN
114             time_restart = time_restart + dt_restart
115          ELSE
116             time_restart = 9999999.9
117          ENDIF
118
119          WRITE( message_string, * ) 'run will be terminated due to user ', &
120                                  'settings of',                            &
121                                  '&restart_time / dt_restart',             &
122                                  '&new restart time is: ', time_restart, ' s' 
123          CALL message( 'check_for_restart', 'PA0164', 0, 0, 0, 6, 0 )
124 
125!
126!--       In case of coupled runs inform the remote model of the termination
127!--       and its reason, provided the remote model has not already been
128!--       informed of another termination reason (terminate_coupled > 0) before,
129!--       or vice versa (terminate_coupled_remote > 0).
130          IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0  &
131               .AND.  terminate_coupled_remote == 0 )  THEN
132
133             IF ( dt_restart /= 9999999.9 )  THEN
134                terminate_coupled = 4
135             ELSE
136                terminate_coupled = 5
137             ENDIF
138#if defined( __parallel )
139             CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,    &
140                                target_id,  0,                               &
141                                terminate_coupled_remote, 1, MPI_INTEGER,    &
142                                target_id,  0,                               &
143                                comm_inter, status, ierr )
144#endif
145          ENDIF
146       ELSE
147          time_restart = 9999999.9
148       ENDIF
149    ENDIF
150
151!
152!-- If the run is stopped, set a flag file which is necessary to initiate
153!-- the start of a continuation run
154    IF ( terminate_run  .AND.  myid == 0 )  THEN
155
156       OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' )
157       WRITE ( 90, '(A)' )  TRIM( run_description_header )
158       CLOSE ( 90 )
159
160    ENDIF
161
162
163 END SUBROUTINE check_for_restart
Note: See TracBrowser for help on using the repository browser.