Skip to content
Snippets Groups Projects
Commit 9573a9db authored by Antoine Cyril David Hoffmann's avatar Antoine Cyril David Hoffmann
Browse files

naming change of comm_r to comm_kr

parent 7b770777
No related branches found
No related tags found
No related merge requests found
......@@ -36,7 +36,7 @@ subroutine auxval
IF (my_id .EQ. 0) WRITE(*,'(A9,I3,A10,I3,A10,I3)') 'n_procs= ', num_procs, ', num_procs_p = ', num_procs_p, ', num_procs_kr = ', num_procs_kr
IF (my_id .EQ. 0) WRITE(*,*) ''
WRITE(*,'(A9,I3,A10,I3,A10,I3)')&
'my_id = ', my_id, ', rank_p = ', rank_p, ', rank_r = ', rank_r
'my_id = ', my_id, ', rank_p = ', rank_p, ', rank_kr = ', rank_kr
WRITE(*,'(A22,I3,A10,I3)')&
' ips_e = ', ips_e, ', ikrs = ', ikrs
WRITE(*,'(A22,I3,A10,I3)')&
......
......@@ -27,7 +27,7 @@ MODULE basic
INTEGER :: num_procs ! number of MPI processes
INTEGER :: num_procs_p ! Number of processes in p
INTEGER :: num_procs_kr ! Number of processes in r
INTEGER :: rank_0, rank_p, rank_r! Ranks in comm0, comm_p, comm_kr
INTEGER :: rank_0, rank_p, rank_kr! Ranks in comm0, comm_p, comm_kr
INTEGER :: nbr_L, nbr_R ! Left and right neighbours (along p)
INTEGER :: nbr_T, nbr_B ! Top and bottom neighbours (along kr)
......
......@@ -47,9 +47,6 @@ MODULE grid
REAL(dp), DIMENSION(:), ALLOCATABLE, PUBLIC :: krarray
REAL(dp), DIMENSION(:), ALLOCATABLE, PUBLIC :: kzarray
REAL(dp), DIMENSION(:), ALLOCATABLE, PUBLIC :: kparray ! kperp array
REAL(dp), DIMENSION(:,:), ALLOCATABLE, PUBLIC :: kparray_2D ! kperp array in 2D
INTEGER, DIMENSION(:), ALLOCATABLE, PUBLIC :: ikparray ! kperp indices array
INTEGER, DIMENSION(:,:), ALLOCATABLE, PUBLIC :: ikparray_2D ! to convert (ikr,ikz) -> ikp
REAL(dp), PUBLIC, PROTECTED :: deltakr, deltakz
INTEGER, PUBLIC, PROTECTED :: ikrs, ikre, ikzs, ikze, ikps, ikpe
INTEGER, PUBLIC, PROTECTED :: ikr_0, ikz_0 ! Indices of k-grid origin
......@@ -82,9 +79,9 @@ CONTAINS
! write(*,*) Nr
local_nkr = (Nr/2+1)/num_procs_kr
! write(*,*) local_nkr
local_nkr_offset = rank_r*local_nkr
local_nkr_offset = rank_kr*local_nkr
if (rank_r .EQ. num_procs_kr-1) local_nkr = (Nr/2+1)-local_nkr_offset
if (rank_kr .EQ. num_procs_kr-1) local_nkr = (Nr/2+1)-local_nkr_offset
END SUBROUTINE init_1Dgrid_distr
......@@ -111,8 +108,6 @@ CONTAINS
counts_np_i(in+1) = iend-istart+1
displs_np_i(in+1) = istart-1
ENDDO
write(*,*) rank_p, ': counts = ', counts_np_e
write(*,*) rank_p, ': disps = ', displs_np_e
! local grid computation
ALLOCATE(parray_e(ips_e:ipe_e))
......@@ -227,36 +222,20 @@ CONTAINS
SUBROUTINE set_kpgrid !Precompute the grid of kperp
IMPLICIT NONE
INTEGER :: ikz_sym, tmp_, counter
! 2D to 1D indices array convertor
ALLOCATE(ikparray_2D(ikrs:ikre,ikzs:ikze))
ALLOCATE( kparray_2D(ikrs:ikre,ikzs:ikze))
REAL(dp):: local_kp_min, local_kp_max
! Find the min and max kperp to load subsequent GK matrices
local_kp_min = krarray(ikrs) !smallest local kperp is on the kr axis
local_kp_max = SQRT(krarray(ikre)**2 + kzarray(Nkz/2+1)**2)
ikps = ikrs
ikpe = INT(CEILING(local_kp_max/deltakr))+2
! local number of different kperp
local_nkp = local_nkr * (local_nkr-1)/2 + 1
local_nkp = ikpe - ikps + 1
! Allocate 1D array of kperp values and indices
ALLOCATE(ikparray(1:local_nkr))
ALLOCATE( kparray(1:local_nkr))
! Fill the arrays
tmp_ = 0; counter = 1
DO ikz = ikzs,ikze
DO ikr = ikrs,ikre
! Set a symmetry on kz
IF (ikz .LE. Nkz/2+1) THEN
ikz_sym = ikz
ELSE
ikz_sym = Nkz+2 - ikz
ENDIF
! Formula to find the 2D to 1D kperp equivalences ordered as
! 10
! 6 9
! 3 5 8
!1 2 4 7 etc...
ikp = MAX(ikr-1,ikz_sym-1)*MIN(ikr-1,ikz_sym-1)/2 + min(ikr-1,ikz_sym-1)
ikparray_2D(ikr,ikz) = ikp
kparray_2D(ikr,ikz) = SQRT(krarray(ikr)**2 + kzarray(ikz)**2)
ENDDO
ALLOCATE(kparray(ikps:ikpe))
DO ikp = ikps,ikpe
kparray(ikp) = REAL(ikp-1,dp) * deltakr
ENDDO
write(*,*) rank_kr, ': ikps = ', ikps, 'ikpe = ',ikpe
END SUBROUTINE
SUBROUTINE grid_readinputs
......
......@@ -61,7 +61,7 @@ SUBROUTINE ppinit
CALL MPI_CART_SUB (comm0, (/.FALSE.,.TRUE./), comm_kr, ierr)
! Find id inside the sub communicators
CALL MPI_COMM_RANK(comm_p, rank_p, ierr)
CALL MPI_COMM_RANK(comm_kr, rank_r, ierr)
CALL MPI_COMM_RANK(comm_kr, rank_kr, ierr)
! Find neighbours
CALL MPI_CART_SHIFT(comm0, 0, 1, nbr_L, nbr_R, ierr)
CALL MPI_CART_SHIFT(comm0, 1, 1, nbr_B, nbr_T, ierr)
......
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