SUBROUTINE tesend ! ! Test for run completion ! USE basic ! IMPLICIT NONE ! ! Local vars and arrays CHARACTER(len=*), PARAMETER :: stop_file = 'mystop' LOGICAL :: mlexist REAL(kind=db) :: eltime, step_time, tremain INTEGER :: rem_steps, reason !________________________________________________________________________________ !!$ WRITE(*,'(a/)') '=== Test for run completion ===' !________________________________________________________________________________ ! 1. Some processors had set nlend ! IF( nlend ) THEN WRITE(*,'(/a)') 'NLEND set to .TRUE.!' RETURN END IF !________________________________________________________________________________ ! 2. NRUN modified through "stop file" ! CALL MPI_BARRIER(MPI_COMM_WORLD, ierr) INQUIRE(file=stop_file, exist=mlexist) IF( mlexist ) THEN IF(mpirank .eq. 0) THEN OPEN(lu_stop, file=stop_file) READ(lu_stop,*,IOSTAT=reason) rem_steps ! Modify remaining steps "on the fly" if(reason .ne. 0 ) rem_steps=10 ! We reached end of file CALL MPI_Bcast(rem_steps, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr) WRITE(*,'(/,/a,i6,a,i8,/,/)') '############ Stop file found: will exit in', rem_steps, ' steps at',step+rem_steps CLOSE(lu_stop, status='delete') ELSE CALL MPI_Bcast(rem_steps, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr) END IF nrun = step + rem_steps END IF !________________________________________________________________________________ ! 3. Test on NRUN ! nlend = step .GE. nrun IF ( nlend ) THEN WRITE(*,'(/a)') 'NRUN steps done' RETURN END IF !________________________________________________________________________________ ! 4. Test on TMAX ! nlend = time .GE. tmax IF ( nlend ) THEN WRITE(*,'(/a)') 'TMAX reached' RETURN END IF !________________________________________________________________________________ ! 5. Test on time allocated to job ! CALL timera(-1, '', eltime) ! Current elapsed time tremain = job_time - eltime ! CALL timera(1, 'Main loop', step_time) step_time = 1.2 * step_time / step ! Averaged time per step + 20% ! nlend = tremain .LT. (step_time+extra_time) IF( nlend ) THEN WRITE(*,'(/a,f8.3)') 'Allocated Job time exhausted:, remaining time =', tremain END IF RETURN ! nlend = .FALSE. !________________________________________________________________________________ END SUBROUTINE tesend