Skip to content
Snippets Groups Projects
Commit d9c7b158 authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann :seedling:
Browse files

remove useless routine

parent e361dc68
No related branches found
No related tags found
No related merge requests found
......@@ -494,81 +494,6 @@ CONTAINS
ENDDO
ENDDO
contains
! Update (and communicate) ghosts of the metric arrays
SUBROUTINE update_ghosts_z(fz_,eo,periodic)
IMPLICIT NONE
! INTEGER, INTENT(IN) :: nztot_
REAL(xp), DIMENSION(local_nz+ngz), INTENT(INOUT) :: fz_
LOGICAL, INTENT(IN) :: periodic
INTEGER, INTENT(IN) :: eo !even/odd z grid
REAL(xp), DIMENSION(-ngz/2:ngz/2) :: buff
INTEGER :: status(MPI_STATUS_SIZE), count, last, first, ig
REAL(xp):: dfdz, beta, z1, z2, f1, f2, z3, f3
first= 1 + ngz/2
last = local_nz+ngz/2
count = 1 ! one point to exchange
IF (num_procs_z .GT. 1) THEN
CALL MPI_BARRIER(MPI_COMM_WORLD,ierr)
!!!!!!!!!!! Send ghost to up neighbour !!!!!!!!!!!!!!!!!!!!!!
DO ig = 1,ngz/2
CALL mpi_sendrecv(fz_(last-(ig-1)), count, mpi_xp_r, nbr_U, 1206+ig, & ! Send to Up the last
buff(-ig), count, mpi_xp_r, nbr_D, 1206+ig, & ! Receive from Down the first-1
comm0, status, ierr)
ENDDO
!!!!!!!!!!! Send ghost to down neighbour !!!!!!!!!!!!!!!!!!!!!!\
DO ig = 1,ngz/2
CALL mpi_sendrecv(fz_(first+(ig-1)), count, mpi_xp_r, nbr_D, 1208+ig, & ! Send to Down the first
buff(ig), count, mpi_xp_r, nbr_U, 1208+ig, & ! Recieve from Up the last+1
comm0, status, ierr)
ENDDO
ELSE
DO ig = 1,ngz/2
buff(-ig) = fz_(last-(ig-1))
buff( ig) = fz_(first+(ig-1))
ENDDO
ENDIF
! if the metric is not periodic, we extrapolate it linearly
IF(.NOT. periodic) THEN
!!!! Right side
! extrapolation from a linear fit
! g(z) = dfdz*(z-z1) + f1
f1 = fz_(last-1)
f2 = fz_(last)
z1 = zarray(last-1,eo)
z2 = zarray(last,eo)
dfdz = (f2-f1)/(z2-z1) ! slope
beta = f1 ! shift
! right ghosts values
DO ig = 1,ngz/2
z3 = z2 + REAL(ig,xp)*(z2 - z1) ! z3 = z2 + ig * dz
f3 = dfdz*(z3 - z1) + beta
buff(ig) = f3
ENDDO
!!!! Left side
! extrapolation from a linear fit
! g(z) = dfdz*(z-z1) + f1
f1 = fz_(first)
f2 = fz_(first+1)
z1 = zarray(first,eo)
z2 = zarray(first+1,eo)
dfdz = (f2-f1)/(z2-z1) ! slope
beta = f1 ! shift
! right ghosts values
DO ig = 1,ngz/2
z3 = z1 - REAL(ig,xp)*(z2 - z1) ! z3 = z1 - ig * dz
f3 = dfdz*(z3 -z1) + beta
buff(-ig) = f3
ENDDO
ENDIF
! Updating ghosts
DO ig = 1,ngz/2
fz_(last +ig) = buff(ig)
fz_(first-ig) = buff(-ig)
ENDDO
! print*,fz_
END SUBROUTINE update_ghosts_z
!> Generate an equidistant array from min to max with n points
function linspace(min,max,n) result(out)
real(xp), INTENT(IN):: min, max
......
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