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

clearer implementation of bracket and sum fonction

parent 07d95da8
No related branches found
No related tags found
No related merge requests found
......@@ -76,10 +76,11 @@ MODULE fourier
!!! Compute the poisson bracket of [F,G] to real space
! - Compute the convolution using the convolution theorem
SUBROUTINE poisson_bracket_and_sum( F_, G_)
SUBROUTINE poisson_bracket_and_sum( F_, G_, sum_real_)
IMPLICIT NONE
COMPLEX(C_DOUBLE_COMPLEX), DIMENSION(ikys:ikye,ikxs:ikxe),&
INTENT(IN) :: F_, G_ ! input fields
INTENT(IN) :: F_, G_ ! input fields
real(C_DOUBLE), pointer, INTENT(INOUT) :: sum_real_(:,:)
! First term df/dx x dg/dy
DO ikx = ikxs, ikxe
DO iky = ikys, ikye
......@@ -91,7 +92,7 @@ MODULE fourier
ENDDO
call fftw_mpi_execute_dft_c2r(planb, cmpx_data_f, real_data_f)
call fftw_mpi_execute_dft_c2r(planb, cmpx_data_g, real_data_g)
bracket_sum_r = bracket_sum_r + real_data_f * real_data_g*inv_Ny*inv_Nx
sum_real_ = sum_real_ + real_data_f * real_data_g*inv_Ny*inv_Nx
! Second term -df/dy x dg/dx
DO ikx = ikxs, ikxe
DO iky = ikys, ikye
......@@ -103,7 +104,7 @@ MODULE fourier
ENDDO
call fftw_mpi_execute_dft_c2r(planb, cmpx_data_f, real_data_f)
call fftw_mpi_execute_dft_c2r(planb, cmpx_data_g, real_data_g)
bracket_sum_r = bracket_sum_r - real_data_f * real_data_g*inv_Ny*inv_Nx
sum_real_ = sum_real_ - real_data_f * real_data_g*inv_Ny*inv_Nx
END SUBROUTINE poisson_bracket_and_sum
!!! Compute the poisson bracket of [F,G] to real space
......
......@@ -98,8 +98,8 @@ SUBROUTINE compute_nonlinear
G_cmpx(ikys:ikye,ikxs:ikxe) = G_cmpx(ikys:ikye,ikxs:ikxe) + &
dnjs(in,ij,is) * moments_e(ip,is,ikys:ikye,ikxs:ikxe,iz,updatetlevel)
ENDDO
!/!\ this function add its result to bracket_sum_r (hard to read sorry) /!\
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx)
!/!\ this function add its result to bracket_sum_r /!\
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx,bracket_sum_r)
!-----------!! ELECTROMAGNETIC CONTRIBUTION -sqrt(tau)/sigma*{Sum_s dnjs [sqrt(p+1)Nap+1s + sqrt(p)Nap-1s], Kernel psi}
IF(EM) THEN
......@@ -114,7 +114,7 @@ SUBROUTINE compute_nonlinear
+sqrt_p *moments_e(ip-1,is,ikys:ikye,ikxs:ikxe,iz,updatetlevel))
ENDDO
!/!\ this function add its result to bracket_sum_r (hard to read sorry) /!\
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx)
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx,bracket_sum_r)
ENDIF
ENDDO nloope
......@@ -162,7 +162,7 @@ ENDIF
dnjs(in,ij,is) * moments_i(ip,is,ikys:ikye,ikxs:ikxe,iz,updatetlevel)
ENDDO
!/!\ this function add its result to bracket_sum_r (hard to read sorry) /!\
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx)
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx,bracket_sum_r)
!-----------!! ELECTROMAGNETIC CONTRIBUTION -sqrt(tau)/sigma*{Sum_s dnjs [sqrt(p+1)Nap+1s + sqrt(p)Nap-1s], Kernel psi}
IF(EM) THEN
! First convolution terms
......@@ -176,7 +176,7 @@ ENDIF
+sqrt_p *moments_i(ip-1,is,ikys:ikye,ikxs:ikxe,iz,updatetlevel))
ENDDO
!/!\ this function add its result to bracket_sum_r (hard to read sorry) /!\
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx)
CALL poisson_bracket_and_sum(F_cmpx,G_cmpx,bracket_sum_r)
ENDIF
ENDDO nloopi
! Put the real nonlinear product into k-space
......
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