From 90496ed715c0fe0066bc0b53e9cedd113e1f8b22 Mon Sep 17 00:00:00 2001
From: Antoine Hoffmann <antoine.hoffmann@epfl.ch>
Date: Tue, 17 Jan 2023 10:35:15 +0100
Subject: [PATCH] standardization of error stop

---
 src/calculus_mod.F90  | 2 +-
 src/closure_mod.F90   | 2 +-
 src/collision_mod.F90 | 2 +-
 src/fourier_mod.F90   | 3 +--
 src/geometry_mod.F90  | 4 ++--
 src/grid_mod.F90      | 4 ++--
 src/miller_mod.F90    | 4 ++--
 src/nonlinear_mod.F90 | 3 +--
 8 files changed, 11 insertions(+), 13 deletions(-)

diff --git a/src/calculus_mod.F90 b/src/calculus_mod.F90
index a724845d..72ff5ffa 100644
--- a/src/calculus_mod.F90
+++ b/src/calculus_mod.F90
@@ -165,7 +165,7 @@ SUBROUTINE simpson_rule_z(f,intf)
 
  ELSE !3D fluxtube
    IF(mod(Nz,2) .ne. 0 ) THEN
-      ERROR STOP 'Simpson rule: Nz must be an even number  !!!!'
+      ERROR STOP '>> ERROR << Simpson rule: Nz must be an even number  !!!!'
    ENDIF
    ! Buil local sum using the weights of composite Simpson's rule
    local_int = 0._dp
diff --git a/src/closure_mod.F90 b/src/closure_mod.F90
index ad7eac91..6a3225b9 100644
--- a/src/closure_mod.F90
+++ b/src/closure_mod.F90
@@ -47,7 +47,7 @@ SUBROUTINE apply_closure_model
     ! + ghosts truncation
     CALL ghosts_upper_truncation
   ELSE
-    ERROR STOP '! Closure scheme not found !'
+    ERROR STOP '>> ERROR << Closure scheme not found '
 
   ENDIF
 
diff --git a/src/collision_mod.F90 b/src/collision_mod.F90
index 251b4f84..536cbeb9 100644
--- a/src/collision_mod.F90
+++ b/src/collision_mod.F90
@@ -53,7 +53,7 @@ CONTAINS
         cosolver_coll = .false.
         interspecies  = .false.
       CASE DEFAULT
-        ERROR STOP 'Error stop: collision model not recognized!!'
+        ERROR STOP '>> ERROR << collision model not recognized!!'
     END SELECT
 
   END SUBROUTINE collision_readinputs
diff --git a/src/fourier_mod.F90 b/src/fourier_mod.F90
index 6a51df0a..97d1b846 100644
--- a/src/fourier_mod.F90
+++ b/src/fourier_mod.F90
@@ -68,8 +68,7 @@ MODULE fourier
     planb = fftw_mpi_plan_dft_c2r_2D(NX_, NY_, cmpx_data_f, real_data_f, communicator,  ior(FFTW_MEASURE, FFTW_MPI_TRANSPOSED_IN))
 
    if ((.not. c_associated(planf)) .OR. (.not. c_associated(planb))) then
-      IF (my_id .EQ. 0) write(*,*) "plan creation error!!"
-      stop
+      ERROR STOP '>> ERROR << plan creation error!!'
    end if
 
   END SUBROUTINE init_grid_distr_and_plans
diff --git a/src/geometry_mod.F90 b/src/geometry_mod.F90
index a077661a..9774219b 100644
--- a/src/geometry_mod.F90
+++ b/src/geometry_mod.F90
@@ -89,7 +89,7 @@ CONTAINS
       CASE ('shearless')
       CASE ('disconnected')
       CASE DEFAULT
-        stop 'Parallel BC not recognized'
+        ERROR STOP '>> ERROR << Parallel BC not recognized'
     END SELECT
     IF(my_id .EQ. 0) print*, 'Parallel BC : ', parallel_bc
 
@@ -126,7 +126,7 @@ CONTAINS
                dBdx,dBdy,hatB,jacobian,dBdz,hatR,hatZ,dxdR,dxdZ,&
                Ckxky,gradz_coeff)
         CASE DEFAULT
-          STOP 'geometry not recognized!!'
+          ERROR STOP '>> ERROR << geometry not recognized!!'
         END SELECT
     ENDIF
     !
diff --git a/src/grid_mod.F90 b/src/grid_mod.F90
index 191b319f..87bd26c0 100644
--- a/src/grid_mod.F90
+++ b/src/grid_mod.F90
@@ -518,7 +518,7 @@ CONTAINS
     END DO
     !! Parallel data distribution
     IF( (Nz .EQ. 1) .AND. (num_procs_z .GT. 1) ) &
-    stop '>>STOPPED<< Cannot have multiple core in z-direction (Nz = 1)'
+    ERROR STOP '>> ERROR << Cannot have multiple core in z-direction (Nz = 1)'
     ! Local data distribution
     CALL decomp1D(total_nz, num_procs_z, rank_z, izs, ize)
     local_nz = ize - izs + 1
@@ -529,7 +529,7 @@ CONTAINS
     ELSEIF(Nz .GE. 4) THEN
       izgs = izs - 2; izge = ize + 2;
     ELSE
-      ERROR STOP 'Error stop: Nz is not appropriate!!'
+      ERROR STOP '>> ERROR << Nz is not appropriate!!'
     ENDIF
     ! List of shift and local numbers between the different processes (used in scatterv and gatherv)
     ALLOCATE(counts_nz (1:num_procs_z))
diff --git a/src/miller_mod.F90 b/src/miller_mod.F90
index c9594b76..34a175cd 100644
--- a/src/miller_mod.F90
+++ b/src/miller_mod.F90
@@ -109,7 +109,7 @@ CONTAINS
     np_s = 500*Npol_s
 
     rho = trpeps*major_R
-    if (rho.le.0.0) stop 'flux surface radius not defined'
+    if (rho.le.0.0) ERROR STOP '>> ERROR << flux surface radius not defined'
     trpeps = rho/major_R
 
     q0 = sign_Ip_CW * sign_Bt_CW * abs(q0)
@@ -437,7 +437,7 @@ CONTAINS
     else
        !new parallel coordinate chi_out==zprime
        !see also tracer_aux.F90
-       if (Npol>1) STOP "ERROR: Npol>1 has not been implemented for edge_opt=\=0.0"
+       if (Npol>1) ERROR STOP '>> ERROR << Npol>1 has not been implemented for edge_opt=\=0.0'
        do k=izs,ize
           chi_out(k)=sinh((-pi+k*2.*pi/Nz)*log(edge_opt*pi+sqrt(edge_opt**2*pi**2+1))/pi)/edge_opt
        enddo
diff --git a/src/nonlinear_mod.F90 b/src/nonlinear_mod.F90
index 61547176..40069470 100644
--- a/src/nonlinear_mod.F90
+++ b/src/nonlinear_mod.F90
@@ -54,8 +54,7 @@ SUBROUTINE compute_Sapj
     CASE ('linear')
       Sepj = 0._dp; Sipj = 0._dp
     CASE DEFAULT
-      IF(my_id.EQ.0) write(*,*) '/!\ Linearity not recognized /!\'
-      stop
+      ERROR STOP '>> ERROR << Linearity not recognized '
   END SELECT
 
   ! Execution time END
-- 
GitLab