Skip to content
Snippets Groups Projects
Commit 92ffdefc authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann
Browse files

update finish conditions

parent 8330ee6b
No related branches found
No related tags found
No related merge requests found
...@@ -65,8 +65,10 @@ SUBROUTINE control ...@@ -65,8 +65,10 @@ SUBROUTINE control
CALL cpu_time(t1_diag); tc_diag = tc_diag + (t1_diag - t0_diag) CALL cpu_time(t1_diag); tc_diag = tc_diag + (t1_diag - t0_diag)
CALL cpu_time(t1_step); tc_step = tc_step + (t1_step - t0_step) CALL cpu_time(t1_step); tc_step = tc_step + (t1_step - t0_step)
END DO END DO
CALL mpi_barrier(MPI_COMM_WORLD,ierr)
IF (my_id .EQ. 1) WRITE(*,'(a/)') '...time integration done' IF (my_id .EQ. 1) WRITE(*,'(a/)') '...time integration done'
!________________________________________________________________________________ !________________________________________________________________________________
! 9. Epilogue ! 9. Epilogue
......
...@@ -6,13 +6,15 @@ SUBROUTINE tesend ...@@ -6,13 +6,15 @@ SUBROUTINE tesend
use prec_const use prec_const
IMPLICIT NONE IMPLICIT NONE
LOGICAL :: mlend LOGICAL :: mlend
real :: tnow
!________________________________________________________________________________ !________________________________________________________________________________
! 1. Some processors had set nlend ! 1. Some processors had set nlend
CALL mpi_allreduce(nlend, mlend, 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, & CALL mpi_allreduce(nlend, mlend, 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, &
& ierr) & ierr)
IF( nlend ) THEN IF( mlend ) THEN
WRITE(*,'(/a)') 'rhs are NaN/Inf' nlend = .TRUE.
IF (my_id .EQ. 0) WRITE(*,'(/a)') 'rhs are NaN/Inf'
IF (my_id .EQ. 0) WRITE(*,*) 'Run terminated at cstep=',cstep IF (my_id .EQ. 0) WRITE(*,*) 'Run terminated at cstep=',cstep
RETURN RETURN
END IF END IF
...@@ -38,12 +40,15 @@ SUBROUTINE tesend ...@@ -38,12 +40,15 @@ SUBROUTINE tesend
!________________________________________________________________________________ !________________________________________________________________________________
! 4. Test on rune time ! 4. Test on rune time
CALL cpu_time(finish) CALL cpu_time(tnow)
nlend = 1.1*(finish-start) .GT. maxruntime mlend = (1.2*(tnow-start)) .GT. maxruntime
CALL mpi_allreduce(mlend, nlend, 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, &
& ierr)
IF ( nlend ) THEN IF ( nlend ) THEN
IF (my_id .EQ. 0) WRITE(*,'(/a)') 'Max run time reached' WRITE(*,'(/a)') 'Max run time reached'
RETURN RETURN
END IF END IF
! !
RETURN
! !
END SUBROUTINE tesend END SUBROUTINE tesend
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Please register or to comment