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
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)
END DO
CALL mpi_barrier(MPI_COMM_WORLD,ierr)
IF (my_id .EQ. 1) WRITE(*,'(a/)') '...time integration done'
!________________________________________________________________________________
! 9. Epilogue
......
......@@ -6,13 +6,15 @@ SUBROUTINE tesend
use prec_const
IMPLICIT NONE
LOGICAL :: mlend
real :: tnow
!________________________________________________________________________________
! 1. Some processors had set nlend
CALL mpi_allreduce(nlend, mlend, 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, &
& ierr)
IF( nlend ) THEN
WRITE(*,'(/a)') 'rhs are NaN/Inf'
IF( mlend ) THEN
nlend = .TRUE.
IF (my_id .EQ. 0) WRITE(*,'(/a)') 'rhs are NaN/Inf'
IF (my_id .EQ. 0) WRITE(*,*) 'Run terminated at cstep=',cstep
RETURN
END IF
......@@ -38,12 +40,15 @@ SUBROUTINE tesend
!________________________________________________________________________________
! 4. Test on rune time
CALL cpu_time(finish)
nlend = 1.1*(finish-start) .GT. maxruntime
CALL cpu_time(tnow)
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 (my_id .EQ. 0) WRITE(*,'(/a)') 'Max run time reached'
WRITE(*,'(/a)') 'Max run time reached'
RETURN
END IF
!
RETURN
!
END SUBROUTINE tesend
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment