Subroutine for interpolating the pre-computed, axisymmetric plasma profiles to the particles' position.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
real(kind=rp), | intent(in), | DIMENSION(:,:), ALLOCATABLE | :: | Y | Particles' position in cylindrical coordinates, Y(1,:) = , Y(2,:) = , and Y(3,:) = . |
|
real(kind=rp), | intent(inout), | DIMENSION(:), ALLOCATABLE | :: | ne | Interpolated background electron density !!. |
|
real(kind=rp), | intent(inout), | DIMENSION(:), ALLOCATABLE | :: | Te | Interpolated background electron temperature . |
|
real(kind=rp), | intent(inout), | DIMENSION(:), ALLOCATABLE | :: | Zeff | Interpolated effective charge number . |
|
integer(kind=is), | intent(inout), | DIMENSION(:), ALLOCATABLE | :: | flag | Flag that indicates whether particles are followed in the simulation (flag=1), or not (flag=0). |
subroutine interp_2D_profiles(Y,ne,Te,Zeff,flag)
!! @note Subroutine for interpolating the pre-computed, axisymmetric
!! plasma profiles to the particles' position. @endnote
REAL(rp), DIMENSION(:,:), ALLOCATABLE, INTENT(IN) :: Y
!! Particles' position in cylindrical coordinates,
!! Y(1,:) = \(R\), Y(2,:) = \(\phi\), and Y(3,:) = \(Z\).
REAL(rp), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: ne
!! Interpolated background electron density !!\(n_e(R,Z)\).
REAL(rp), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: Te
!! Interpolated background electron temperature \(T_e(R,Z)\).
REAL(rp), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: Zeff
!! Interpolated effective charge number \(Z_{eff}(R,Z)\).
INTEGER(is), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: flag
!! Flag that indicates whether particles are followed in the
!! simulation (flag=1), or not (flag=0).
INTEGER :: pp
!! Particle iterator.
INTEGER :: ss
!! Species iterator.
if (size(Y,1).eq.1) then
ss = size(Y,1)
else
if (Y(2,1).eq.0) then
ss=1_idef
else
ss = size(Y,1)
end if
endif
! write(output_unit_write,'("Also R_buffer: ",E17.10)') Y(1,ss)
!$OMP PARALLEL DO FIRSTPRIVATE(ss) PRIVATE(pp,ezerr) &
!$OMP& SHARED(Y,ne,Te,Zeff,flag,profiles_2d)
do pp=1_idef,ss
if ( flag(pp) .EQ. 1_is ) then
call EZspline_interp(profiles_2d%ne, Y(pp,1), Y(pp,3), ne(pp), ezerr)
call EZspline_error(ezerr)
! write(output_unit_write,'("Also R_buffer: ",E17.10)') Y(pp,1)
if (ezerr .NE. 0) then ! We flag the particle as lost
flag(pp) = 0_is
end if
call EZspline_interp(profiles_2d%Te, Y(pp,1), Y(pp,3), Te(pp), ezerr)
call EZspline_error(ezerr)
call EZspline_interp(profiles_2d%Zeff, Y(pp,1), Y(pp,3), Zeff(pp), ezerr)
call EZspline_error(ezerr)
end if
end do
!$OMP END PARALLEL DO
end subroutine interp_2D_profiles