Ignore:
Timestamp:
Sep 24, 2014 2:06:57 PM (10 years ago)
Author:
maronga
Message:

New flag files allow to force unscheduled termination/restarts of batch jobs, progress output is made for batch runs, small adjustments for lxce6 and lccrayh/lccrayb

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/check_for_restart.f90

    r1354 r1468  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Added support for unscheduled job termination using the flag files
     23! DO_STOP_NOW and DO_RESTART_NOW
    2324!
    2425! Former revisions:
     
    6566
    6667
    67     LOGICAL :: terminate_run_l  !:
     68    LOGICAL :: terminate_run_l           !:
     69    LOGICAL :: do_stop_now = .FALSE.     !:
     70    LOGICAL :: do_restart_now = .FALSE.  !:
    6871
    6972    REAL(wp) ::  remaining_time !:
     
    113116
    114117       terminate_coupled = 3
     118
    115119#if defined( __parallel )
    116120       IF ( myid == 0 ) THEN
     
    126130    ENDIF
    127131
    128 !
    129 !-- Set the stop flag also, if restart is forced by user
    130     IF ( time_restart /= 9999999.9_wp  .AND.                                      &
     132
     133!
     134!-- Check if a flag file exists that forces a termination of the model
     135    terminate_run_l = .FALSE.
     136    IF ( myid == 0 )  THEN
     137       INQUIRE(FILE="DO_STOP_NOW", EXIST=do_stop_now)
     138       INQUIRE(FILE="DO_RESTART_NOW", EXIST=do_restart_now)
     139
     140       IF ( do_stop_now .OR. do_restart_now )  THEN
     141
     142          terminate_run_l = .TRUE.
     143
     144          WRITE( message_string, * ) 'run will be terminated because user ',   &
     145                                  'forced a job finialization using a flag',   &
     146                                  'file:',                                     &
     147                                  '&DO_STOP_NOW: ', do_stop_now,               &
     148                                  '&DO_RESTART_NOW: ', do_restart_now
     149          CALL message( 'check_for_restart', 'PA0398', 0, 0, 0, 6, 0 )
     150
     151       ENDIF
     152    ENDIF
     153
     154
     155#if defined( __parallel )
     156!
     157!-- Make a logical OR for all processes. Stop the model run if at least
     158!-- one processor has reached the time limit.
     159    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
     160    CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL,        &
     161                        MPI_LOR, comm2d, ierr )
     162#else
     163    terminate_run = terminate_run_l
     164#endif
     165
     166!
     167!-- In case of coupled runs inform the remote model of the termination
     168!-- and its reason, provided the remote model has not already been
     169!-- informed of another termination reason (terminate_coupled > 0) before,
     170!-- or vice versa (terminate_coupled_remote > 0).
     171    IF ( terminate_run .AND. coupling_mode /= 'uncoupled' .AND.                &
     172         terminate_coupled == 0 .AND.  terminate_coupled_remote == 0 )  THEN
     173
     174       terminate_coupled = 6
     175
     176#if defined( __parallel )
     177       IF ( myid == 0 ) THEN
     178          CALL MPI_SENDRECV( terminate_coupled,        1, MPI_INTEGER,      &
     179                             target_id,  0,                                 &
     180                             terminate_coupled_remote, 1, MPI_INTEGER,      &
     181                             target_id,  0,                                 &
     182                             comm_inter, status, ierr )   
     183       ENDIF
     184       CALL MPI_BCAST( terminate_coupled_remote, 1, MPI_INTEGER, 0,         &
     185                       comm2d, ierr ) 
     186#endif
     187
     188    ENDIF
     189
     190!
     191!-- Set the stop flag also, if restart is forced by user settings
     192    IF ( time_restart /= 9999999.9_wp  .AND.                                   &
    131193         time_restart < time_since_reference_point )  THEN
    132194
     
    183245!
    184246!-- If the run is stopped, set a flag file which is necessary to initiate
    185 !-- the start of a continuation run
    186     IF ( terminate_run  .AND.  myid == 0 )  THEN
     247!-- the start of a continuation run, except if the user forced to stop the
     248!-- run without restart
     249    IF ( terminate_run  .AND.  myid == 0 .AND. .NOT. do_stop_now)  THEN
    187250
    188251       OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' )
Note: See TracChangeset for help on using the changeset viewer.