interp_2D_profiles Subroutine

private subroutine interp_2D_profiles(Y, ne, Te, Zeff, flag)

Arguments

Type IntentOptional AttributesName
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).


Calls

proc~~interp_2d_profiles~~CallsGraph proc~interp_2d_profiles interp_2D_profiles ezspline_error ezspline_error proc~interp_2d_profiles->ezspline_error

Called by

proc~~interp_2d_profiles~~CalledByGraph proc~interp_2d_profiles interp_2D_profiles proc~interp_profiles interp_profiles proc~interp_profiles->proc~interp_2d_profiles proc~get_profiles get_profiles proc~get_profiles->proc~interp_profiles proc~avalanche_4d Avalanche_4D proc~avalanche_4d->proc~get_profiles proc~get_avalanche_4d get_Avalanche_4D proc~get_avalanche_4d->proc~avalanche_4d

Contents

Source Code


Source Code

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