From 92ffdefc40b28f2b09fdd785092219c406c56936 Mon Sep 17 00:00:00 2001
From: Antoine Cyril David Hoffmann <ahoffman@spcpc606.epfl.ch>
Date: Thu, 17 Dec 2020 15:45:21 +0100
Subject: [PATCH] update finish conditions

---
 src/control.F90 |  4 +++-
 src/tesend.F90  | 15 ++++++++++-----
 2 files changed, 13 insertions(+), 6 deletions(-)

diff --git a/src/control.F90 b/src/control.F90
index 394fe61e..d95e890f 100644
--- a/src/control.F90
+++ b/src/control.F90
@@ -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
diff --git a/src/tesend.F90 b/src/tesend.F90
index 3ee2acc2..faffab8c 100644
--- a/src/tesend.F90
+++ b/src/tesend.F90
@@ -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
-- 
GitLab