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

cleaning, adiabe is now benchmarked

parent 29d036c6
No related branches found
No related tags found
No related merge requests found
...@@ -27,6 +27,7 @@ SUBROUTINE poisson ...@@ -27,6 +27,7 @@ SUBROUTINE poisson
kxloop: DO ikx = ikxs,ikxe kxloop: DO ikx = ikxs,ikxe
kyloop: DO iky = ikys,ikye kyloop: DO iky = ikys,ikye
phi(iky,ikx,izs:ize) = 0._dp
!!!! Compute ion particle charge density q_i n_i !!!! Compute ion particle charge density q_i n_i
rho_i = 0._dp rho_i = 0._dp
DO ini=1,jmaxi+1 DO ini=1,jmaxi+1
...@@ -43,25 +44,22 @@ SUBROUTINE poisson ...@@ -43,25 +44,22 @@ SUBROUTINE poisson
END DO END DO
ELSE ! Adiabatic electrons ELSE ! Adiabatic electrons
! Adiabatic charge density (linked to flux surface averaged phi) ! Adiabatic charge density (linked to flux surface averaged phi)
fsa_phi = 0._dp
! We compute the flux surface average solving a flux surface averaged ! We compute the flux surface average solving a flux surface averaged
! Poisson equation, i.e. ! Poisson equation, i.e.
!
! [qi^2(1-sum_j K_j^2)/tau_i] <phi>_psi = <q_i n_i >_psi ! [qi^2(1-sum_j K_j^2)/tau_i] <phi>_psi = <q_i n_i >_psi
! inv_pol_ion^-1 fsa_phi = simpson(Jacobian rho_i ) * iInt_Jacobian ! inv_pol_ion^-1 fsa_phi = simpson(Jacobian rho_i ) * iInt_Jacobian
fsa_phi = 0._dp
IF(kyarray(iky).EQ.0._dp) THEN ! take ky=0 mode (y-average) IF(kyarray(iky).EQ.0._dp) THEN ! take ky=0 mode (y-average)
! Prepare integrant for z-average ! Prepare integrant for z-average
integrant(izs:ize) = Jacobian(izs:ize,0)*rho_i(izs:ize)*inv_pol_ion(iky,ikx,izs:ize) integrant(izs:ize) = Jacobian(izs:ize,0)*rho_i(izs:ize)*inv_pol_ion(iky,ikx,izs:ize)
call simpson_rule_z(integrant(izs:ize),intf_) ! get the flux averaged phi call simpson_rule_z(integrant(izs:ize),intf_) ! get the flux averaged phi
fsa_phi = intf_ fsa_phi = intf_ * iInt_Jacobian !Normalize by 1/int(Jxyz)dz
ENDIF ENDIF
rho_e(izs:ize) = fsa_phi * iInt_Jacobian !Normalize by 1/int(Jxyz)dz rho_e(izs:ize) = fsa_phi
ENDIF ENDIF
!!!!!!!!!!!!!!! Inverting the poisson equation !!!!!!!!!!!!!!!!!!!!!!!!!! !!!!!!!!!!!!!!! Inverting the poisson equation !!!!!!!!!!!!!!!!!!!!!!!!!!
DO iz = izs,ize phi(iky,ikx,izs:ize) = (rho_e(izs:ize) + rho_i(izs:ize))*inv_poisson_op(iky,ikx,izs:ize)
phi(iky, ikx, iz) = (rho_e(iz) + rho_i(iz))*inv_poisson_op(iky,ikx,iz)
ENDDO
END DO kyloop END DO kyloop
END DO kxloop END DO kxloop
......
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