SUBROUTINE check_for_restart !------------------------------------------------------------------------------! ! Current revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Id: check_for_restart.f90 392 2009-09-24 10:39:14Z maronga $ ! ! 291 2009-04-16 12:07:26Z raasch ! Coupling with independent precursor runs. ! Output of messages replaced by message handling routine ! ! 222 2009-01-12 16:04:16Z letzel ! Implementation of an MPI-1 coupling: replaced myid with target_id ! Bugfix for nonparallel execution ! ! 108 2007-08-24 15:10:38Z letzel ! modifications to terminate coupled runs ! ! RCS Log replace by Id keyword, revision history cleaned up ! ! Revision 1.11 2007/02/11 12:55:13 raasch ! Informative output to the job protocol ! ! Revision 1.1 1998/03/18 20:06:51 raasch ! Initial revision ! ! ! Description: ! ------------ ! Set stop flag, if restart is neccessary because of expiring cpu-time or ! if it is forced by user !------------------------------------------------------------------------------! USE pegrid USE control_parameters IMPLICIT NONE LOGICAL :: terminate_run_l REAL :: remaining_time ! !-- Check remaining CPU-time CALL local_tremain( remaining_time ) ! !-- If necessary set a flag to stop the model run terminate_run_l = .FALSE. IF ( remaining_time <= termination_time_needed .AND. & write_binary(1:4) == 'true' ) THEN terminate_run_l = .TRUE. ENDIF #if defined( __parallel ) ! !-- Make a logical OR for all processes. Stop the model run if at least !-- one processor has reached the time limit. CALL MPI_ALLREDUCE( terminate_run_l, terminate_run, 1, MPI_LOGICAL, & MPI_LOR, comm2d, ierr ) #else terminate_run = terminate_run_l #endif ! !-- Output that job will be terminated IF ( terminate_run .AND. myid == 0 ) THEN WRITE( message_string, * ) 'run will be terminated because it is ', & 'running out of job cpu limit & ', & 'remaining time: ', remaining_time, ' s', & 'termination time needed:', termination_time_needed, ' s' CALL message( 'check_for_restart', 'PA0163', 0, 1, 0, 6, 0 ) ENDIF ! !-- In case of coupled runs inform the remote model of the termination !-- and its reason, provided the remote model has not already been !-- informed of another termination reason (terminate_coupled > 0) before, !-- or vice versa (terminate_coupled_remote > 0). IF ( terminate_run .AND. TRIM( coupling_mode ) /= 'uncoupled' .AND. & terminate_coupled == 0 .AND. terminate_coupled_remote == 0 ) THEN terminate_coupled = 3 #if defined( __parallel ) CALL MPI_SENDRECV( terminate_coupled, 1, MPI_INTEGER, & target_id, 0, & terminate_coupled_remote, 1, MPI_INTEGER, & target_id, 0, & comm_inter, status, ierr ) #endif ENDIF ! !-- Set the stop flag also, if restart is forced by user IF ( time_restart /= 9999999.9 .AND. & time_restart < time_since_reference_point ) THEN ! !-- Restart is not neccessary, if the end time of the run (given by !-- the user) has been reached IF ( simulated_time < end_time ) THEN terminate_run = .TRUE. ! !-- Increment restart time, if forced by user, otherwise set restart !-- time to default (no user restart) IF ( dt_restart /= 9999999.9 ) THEN time_restart = time_restart + dt_restart ELSE time_restart = 9999999.9 ENDIF WRITE( message_string, * ) 'run will be terminated due to user ', & 'settings of', & '&restart_time / dt_restart', & '&new restart time is: ', time_restart, ' s' CALL message( 'check_for_restart', 'PA0164', 0, 0, 0, 6, 0 ) ! !-- In case of coupled runs inform the remote model of the termination !-- and its reason, provided the remote model has not already been !-- informed of another termination reason (terminate_coupled > 0) before, !-- or vice versa (terminate_coupled_remote > 0). IF ( coupling_mode /= 'uncoupled' .AND. terminate_coupled == 0 & .AND. terminate_coupled_remote == 0 ) THEN IF ( dt_restart /= 9999999.9 ) THEN terminate_coupled = 4 ELSE terminate_coupled = 5 ENDIF #if defined( __parallel ) CALL MPI_SENDRECV( terminate_coupled, 1, MPI_INTEGER, & target_id, 0, & terminate_coupled_remote, 1, MPI_INTEGER, & target_id, 0, & comm_inter, status, ierr ) #endif ENDIF ELSE time_restart = 9999999.9 ENDIF ENDIF ! !-- If the run is stopped, set a flag file which is necessary to initiate !-- the start of a continuation run IF ( terminate_run .AND. myid == 0 ) THEN OPEN ( 90, FILE='CONTINUE_RUN', FORM='FORMATTED' ) WRITE ( 90, '(A)' ) TRIM( run_description_header ) CLOSE ( 90 ) ENDIF END SUBROUTINE check_for_restart