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

fftw 1D implemented

-dirty (lots of uncommented lines)
-unoptimized (could remove aux var)
-ExB factor still not working
parent 27019b9e
No related branches found
No related tags found
No related merge requests found
......@@ -74,7 +74,7 @@ CONTAINS
! Setup nonlinear factor
ALLOCATE( ExB_NL_factor(Nx,local_nky))
ALLOCATE(inv_ExB_NL_factor(Ny/2+2,local_nx))
ALLOCATE(inv_ExB_NL_factor(Ny/2+1,local_nx))
ExB_NL_factor = 1._xp
inv_ExB_NL_factor = 1._xp
......@@ -231,7 +231,7 @@ CONTAINS
ENDDO
ENDDO
! ... and the inverse
DO iky = 1,Ny/2+2 ! WARNING: Global indices ky loop
DO iky = 1,Ny/2+1 ! WARNING: Global indices ky loop
! for readability
J_xp = REAL(iky-1,xp)
IF(J_xp .GT. 0._xp) THEN
......@@ -248,9 +248,6 @@ CONTAINS
! inv_ExB_NL_factor(iky,ix) = EXP(imagu*sky_ExB_full(iky)*xval)
ENDDO
ENDDO
! Cancel the additional point
inv_ExB_NL_factor(Ny/2+1,:) = 0._xp
inv_ExB_NL_factor(Ny/2+2,:) = 0._xp
END SUBROUTINE Update_nonlinear_ExB_factors
END MODULE ExB_shear_flow
\ No newline at end of file
This diff is collapsed.
......@@ -7,7 +7,7 @@ MODULE nonlinear
local_np,ngp,parray,pmax,&
local_nj,ngj,jarray,jmax, local_nj_offset, dmax,&
kyarray, AA_y, local_nky, inv_Ny,&
total_nkx,kxarray, AA_x, inv_Nx,&
total_nkx,kxarray, AA_x, inv_Nx,local_nx, Ny, &
local_nz,ngz,zarray,nzgrid, deltakx, iky0, contains_kx0, contains_ky0
USE model, ONLY : LINEARITY, EM, ikxZF, ZFamp, ExB_NL_CORRECTION
USE closure, ONLY : evolve_mom, nmaxarray
......@@ -56,6 +56,7 @@ SUBROUTINE compute_nonlinear
IMPLICIT NONE
INTEGER :: iz,ij,ip,eo,ia,ikx,iky,izi,ipi,iji,ini,isi
INTEGER :: ikxExBp, ikxExBn ! Negative and positive ExB flow indices
COMPLEX(xp), DIMENSION(Ny/2+1,local_nx) :: invinvfactor ! TEST
z:DO iz = 1,local_nz
izi = iz + ngz/2
j:DO ij = 1,local_nj ! Loop over Laguerre moments
......@@ -122,6 +123,8 @@ SUBROUTINE compute_nonlinear
! Apply the ExB shearing rate factor before going back to k-space
IF (ExB_NL_CORRECTION) THEN
CALL apply_inv_ExB_NL_factor(bracket_sum_r,inv_ExB_NL_factor)
! invinvfactor = 1._xp/inv_ExB_NL_factor
! CALL apply_inv_ExB_NL_factor(bracket_sum_r,invinvfactor)
ENDIF
! Put the real nonlinear product back into k-space
#ifdef SINGLE_PRECISION
......
......@@ -20,13 +20,13 @@ SUBROUTINE stepon
SUBSTEPS:DO num_step=1,ntimelevel ! eg RK4 compute successively k1, k2, k3, k4
!----- TEST !-----
! Update the ExB shear flow for the next step
! This call includes :
! - the ExB shear value (s(ky)) update for the next time step
! - the kx grid update
! - the ExB NL correction factor update (exp(+/- ixkySdts))
! - (optional) the kernel, poisson op. and ampere op update
CALL Update_ExB_shear_flow(num_step)
! ! Update the ExB shear flow for the next step
! ! This call includes :
! ! - the ExB shear value (s(ky)) update for the next time step
! ! - the kx grid update
! ! - the ExB NL correction factor update (exp(+/- ixkySdts))
! ! - (optional) the kernel, poisson op. and ampere op update
! CALL Update_ExB_shear_flow(num_step)
!-----END TEST !-----
!----- BEFORE: All fields+ghosts are updated for step = n
! Compute right hand side from current fields
......
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