SUBROUTINE check_for_restart !------------------------------------------------------------------------------! ! Actual revisions: ! ----------------- ! ! ! Former revisions: ! ----------------- ! $Log: check_for_restart.f90,v $ ! Revision 1.11 2007/02/11 12:55:13 raasch ! Informative output to the job protocol ! ! Revision 1.10 2003/03/16 09:27:49 raasch ! Two underscores (_) are placed in front of all define-strings ! ! Revision 1.9 2002/12/19 13:48:59 raasch ! Stop flag is also set in case of user forced restarts, routine name ! changed from check_cpu_time to check_for_restart, the run description ! header will be written on file CONTINUE_RUN ! ! Revision 1.8 2001/08/21 08:22:23 raasch ! MPI_ALLREDUCE moved out of IF-clause ! ! Revision 1.7 2001/03/30 06:56:28 raasch ! Translation of remaining German identifiers (variables, subroutines, etc.) ! ! Revision 1.6 2001/01/22 05:36:33 raasch ! Module test_variables removed ! ! Revision 1.5 2001/01/02 17:19:27 raasch ! Initial value of terminate_run_l is set to .FALSE. (undefined before). ! Flag file will only be created by PE0. Unit 90 is used instead of 91. ! ! Revision 1.4 2000/01/21 16:27:59 letzel ! All comments translated into English ! ! Revision 1.3 1998/07/06 12:07:47 raasch ! + USE test_variables ! ! Revision 1.2 1998/03/24 15:24:54 raasch ! Lauf wird nur dann beendet und Fortsetzungslauf gestartet, falls auch eine ! Abspeicherung der entsprechenden Binaerdateien vorgesehen ist. ! Beendigung der Rechnung auf mehreren Prozessoren richtig implementiert. ! ! 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 PRINT*, '*** WARNING: run will be terminated because it is running out of job cpu', & 'limit' PRINT*, ' remaining time: ', remaining_time, ' s' PRINT*, ' termination time needed:', termination_time_needed, ' s' ENDIF ! !-- Set the stop flag also, if restart is forced by user IF ( time_restart /= 9999999.9 .AND. time_restart < simulated_time ) & 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 IF ( myid == 0 ) THEN PRINT*, '*** INFORMATIVE: run will be terminated due to user settings of' PRINT*, ' restart_time / dt_restart' PRINT*, ' new restart time is: ', time_restart, ' s' 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