From e30a7e7ee481c7bdc4c1c454da185b349008ff30 Mon Sep 17 00:00:00 2001
From: Antoine Hoffmann <antoine.hoffmann@epfl.ch>
Date: Fri, 1 Jul 2022 11:52:35 +0200
Subject: [PATCH] compressed ghosts routines and ensured sheared=false for
 zpinch

---
 src/geometry_mod.F90 |  3 ++-
 src/ghosts_mod.F90   | 40 ++++++++++++++++------------------------
 src/inital.F90       | 19 ++++++++-----------
 src/stepon.F90       |  7 +++----
 4 files changed, 29 insertions(+), 40 deletions(-)

diff --git a/src/geometry_mod.F90 b/src/geometry_mod.F90
index f2765097..257510d1 100644
--- a/src/geometry_mod.F90
+++ b/src/geometry_mod.F90
@@ -74,6 +74,7 @@ CONTAINS
         CASE('Z-pinch')
           IF( my_id .eq. 0 ) WRITE(*,*) 'Z-pinch geometry'
           call eval_zpinch_geometry
+          SHEARED = .FALSE.
         CASE DEFAULT
           ERROR STOP 'Error stop: geometry not recognized!!'
         END SELECT
@@ -213,7 +214,7 @@ CONTAINS
           ky = kyarray(iky)
            DO ikx= ikxs, ikxe
              kx = kxarray(ikx)
-             Ckxky(iky, ikx, iz,eo) = - ky * hatB(iz,eo) ! .. multiply by hatB to cancel the 1/ hatB factor in moments_eqs_rhs.f90 routine
+             Ckxky(iky, ikx, iz,eo) = -ky * hatB(iz,eo) ! .. multiply by hatB to cancel the 1/ hatB factor in moments_eqs_rhs.f90 routine
            ENDDO
         ENDDO
       ! coefficient in the front of parallel derivative
diff --git a/src/ghosts_mod.F90 b/src/ghosts_mod.F90
index 14da9153..b1822249 100644
--- a/src/ghosts_mod.F90
+++ b/src/ghosts_mod.F90
@@ -10,24 +10,28 @@ IMPLICIT NONE
 
 INTEGER :: status(MPI_STATUS_SIZE), source, dest, count, ipg
 
-PUBLIC :: update_ghosts_p_moments, update_ghosts_z_phi, update_ghosts_z_moments
+PUBLIC :: update_ghosts
 
 CONTAINS
 
-SUBROUTINE update_ghosts_p_moments
-    CALL cpu_time(t0_ghost)
+SUBROUTINE update_ghosts
+  CALL cpu_time(t0_ghost)
 
-    IF (num_procs_p .GT. 1) THEN ! Do it only if we share the p
-        CALL MPI_BARRIER(MPI_COMM_WORLD,ierr)
-        IF(KIN_E) CALL update_ghosts_p_e
+  IF (num_procs_p .GT. 1) THEN ! Do it only if we share the p
+      IF(KIN_E)&
+      CALL update_ghosts_p_e
+      CALL update_ghosts_p_i
+  ENDIF
 
-        CALL MPI_BARRIER(MPI_COMM_WORLD,ierr)
-        CALL update_ghosts_p_i
-    ENDIF
+  IF(Nz .GT. 1) THEN
+    IF(KIN_E) &
+    CALL update_ghosts_z_e
+    CALL update_ghosts_z_i
+    CALL update_ghosts_z_phi
+  ENDIF
 
-    CALL cpu_time(t1_ghost)
-    tc_ghost = tc_ghost + (t1_ghost - t0_ghost)
-END SUBROUTINE update_ghosts_p_moments
+  tc_ghost = tc_ghost + (t1_ghost - t0_ghost)
+END SUBROUTINE update_ghosts
 
 
 !Communicate p+1, p+2 moments to left neighboor and p-1, p-2 moments to right one
@@ -96,18 +100,6 @@ SUBROUTINE update_ghosts_p_i
 
 END SUBROUTINE update_ghosts_p_i
 
-SUBROUTINE update_ghosts_z_moments
-  IMPLICIT NONE
-  CALL cpu_time(t0_ghost)
-    IF(Nz .GT. 1) THEN
-    IF(KIN_E) &
-    CALL update_ghosts_z_e
-    CALL update_ghosts_z_i
-    ENDIF
-    CALL cpu_time(t1_ghost)
-    tc_ghost = tc_ghost + (t1_ghost - t0_ghost)
-END SUBROUTINE update_ghosts_z_moments
-
 !Communicate z+1, z+2 moments to left neighboor and z-1, z-2 moments to right one
 ! [a b|C D|e f] : proc n has moments a to f where a,b,e,f are ghosts
 !
diff --git a/src/inital.F90 b/src/inital.F90
index c0261105..343c4f6d 100644
--- a/src/inital.F90
+++ b/src/inital.F90
@@ -8,8 +8,7 @@ SUBROUTINE inital
   USE time_integration, ONLY: set_updatetlevel
   USE collision,        ONLY: load_COSOlver_mat, cosolver_coll
   USE closure,          ONLY: apply_closure_model
-  USE ghosts,           ONLY: update_ghosts_z_moments, update_ghosts_p_moments, &
-                              update_ghosts_z_phi
+  USE ghosts,           ONLY: update_ghosts
   USE restarts,         ONLY: load_moments, job2load
   USE numerics,         ONLY: play_with_modes, save_EM_ZF_modes
   USE processing,       ONLY: compute_fluid_moments
@@ -24,8 +23,8 @@ SUBROUTINE inital
   IF ( job2load .GE. 0 ) THEN
     IF (my_id .EQ. 0) WRITE(*,*) 'Load moments'
     CALL load_moments ! get N_0
-    CALL update_ghosts_z_moments
     CALL poisson ! compute phi_0=phi(N_0)
+    CALL update_ghosts
   ! through initialization
   ELSE
     SELECT CASE (INIT_OPT)
@@ -33,30 +32,30 @@ SUBROUTINE inital
     CASE ('phi')
       IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy phi'
       CALL init_phi
-      CALL update_ghosts_z_phi
+      CALL update_ghosts
     ! set moments_00 (GC density) with noise and compute phi afterwards
     CASE('mom00')
       IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy gyrocenter density'
       CALL init_gyrodens ! init only gyrocenter density
-      CALL update_ghosts_z_moments
+      CALL update_ghosts
       CALL poisson
     ! init all moments randomly (unadvised)
     CASE('allmom')
       IF (my_id .EQ. 0) WRITE(*,*) 'Init noisy moments'
       CALL init_moments ! init all moments
-      CALL update_ghosts_z_moments
+      CALL update_ghosts
       CALL poisson
     ! init a gaussian blob in gyrodens
     CASE('blob')
       IF (my_id .EQ. 0) WRITE(*,*) '--init a blob'
       CALL initialize_blob
-      CALL update_ghosts_z_moments
+      CALL update_ghosts
       CALL poisson
     ! init moments 00 with a power law similarly to GENE
     CASE('ppj')
       IF (my_id .EQ. 0) WRITE(*,*) 'ppj init ~ GENE'
       call init_ppj
-      CALL update_ghosts_z_moments
+      CALL update_ghosts
       CALL poisson
     END SELECT
   ENDIF
@@ -65,9 +64,7 @@ SUBROUTINE inital
   CALL apply_closure_model
   ! ghosts for p parallelization
   IF (my_id .EQ. 0) WRITE(*,*) 'Ghosts communication'
-  CALL update_ghosts_p_moments
-  CALL update_ghosts_z_moments
-  CALL update_ghosts_z_phi
+  CALL update_ghosts
   !! End of phi and moments initialization
 
   ! Save (kx,0) and (0,ky) modes for num exp
diff --git a/src/stepon.F90 b/src/stepon.F90
index 230f6bf0..7c4ee5f5 100644
--- a/src/stepon.F90
+++ b/src/stepon.F90
@@ -3,7 +3,7 @@ SUBROUTINE stepon
   USE advance_field_routine, ONLY: advance_time_level, advance_field, advance_moments
   USE basic
   USE closure
-  USE ghosts
+  USE ghosts, ONLY: update_ghosts
   USE grid
   USE model, ONLY : LINEARITY, KIN_E
   use prec_const
@@ -32,8 +32,7 @@ SUBROUTINE stepon
       ! Closure enforcement of moments
       CALL apply_closure_model
       ! Exchanges the ghosts values of N_n+1
-      CALL update_ghosts_p_moments
-      CALL update_ghosts_z_moments
+      CALL update_ghosts
 
       ! Update electrostatic potential phi_n = phi(N_n+1)
       CALL poisson
@@ -41,7 +40,7 @@ SUBROUTINE stepon
 
       ! Numerical experiments
       ! Store or cancel/maintain zonal modes artificially
-      CALL play_with_modes
+      ! CALL play_with_modes
 
       !-  Check before next step
       CALL checkfield_all()
-- 
GitLab