gaussian_elliptic_torus Subroutine

private subroutine gaussian_elliptic_torus(params, spp)

@brief Subroutine that generates a Gaussian radial distribution in an elliptic torus as the initial spatial condition of a given particle species in the simulation. @details As a first step, we generate an Gaussian radial distribution in a circular cross-section torus as in \ref korc_spatial_distribution.gaussian_torus. Then we transform this spatial distribution to a one in an torus with an elliptic cross section, this following the same approach as in \ref korc_spatial_distribution.elliptic_torus.

@param[in] params Core KORC simulation parameters. @param[in,out] spp An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation. @param rotation_angle This is the angle in \ref korc_spatial_distribution.elliptic_torus. @param r Radial position of the particles . @param theta Uniform deviates in the range representing the uniform poloidal angle distribution of the particles. @param zeta Uniform deviates in the range representing the uniform toroidal angle distribution of the particles. @param X Auxiliary vector used in the coordinate transformations. @param Y Auxiliary vector used in the coordinate transformations. @param X1 Auxiliary vector used in the coordinate transformations. @param Y1 Auxiliary vector used in the coordinate transformations. @param sigma Standard deviation of the radial distribution function. @param pp Particle iterator.

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
type(SPECIES), intent(inout) :: spp

Calls

proc~~gaussian_elliptic_torus~~CallsGraph proc~gaussian_elliptic_torus gaussian_elliptic_torus proc~init_u_random init_u_random proc~gaussian_elliptic_torus->proc~init_u_random proc~init_random_seed init_random_seed proc~gaussian_elliptic_torus->proc~init_random_seed proc~rand_int64 rand_int64 proc~init_u_random->proc~rand_int64

Contents


Source Code

subroutine gaussian_elliptic_torus(params,spp)
  TYPE(KORC_PARAMS), INTENT(IN) 	:: params
  TYPE(SPECIES), INTENT(INOUT) 		:: spp
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: rotation_angle
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: r
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: theta
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: zeta
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: X
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: Y
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: X1
  REAL(rp), DIMENSION(:), ALLOCATABLE 	:: Y1
  REAL(rp) 				:: sigma
  INTEGER 				:: pp

  ALLOCATE(X1(spp%ppp))
  ALLOCATE(Y1(spp%ppp))
  ALLOCATE(X(spp%ppp))
  ALLOCATE(Y(spp%ppp))
  ALLOCATE( rotation_angle(spp%ppp) )
  ALLOCATE( theta(spp%ppp) )
  ALLOCATE( zeta(spp%ppp) )
  ALLOCATE( r(spp%ppp) )

  ! Initial condition of uniformly distributed particles on a
  ! disk in the xz-plane
  ! A unique velocity direction
  call init_u_random(10986546_8)

  call init_random_seed()
  call RANDOM_NUMBER(theta)
  theta = 2.0_rp*C_PI*theta

  call init_random_seed()
  call RANDOM_NUMBER(zeta)
  zeta = 2.0_rp*C_PI*zeta

  ! Uniform distribution on a disk at a fixed azimuthal theta
  call init_random_seed()
  call RANDOM_NUMBER(r)

  sigma = 1.0_rp/SQRT(2.0_rp*(spp%falloff_rate/params%cpp%length))
  sigma = sigma/params%cpp%length

  r = sigma*SQRT(-2.0_rp*LOG(1.0_rp - (1.0_rp - &
       EXP(-0.5_rp*spp%r_outter**2/sigma**2))*r))
!  spp%vars%X(:,1) = ( spp%Ro + r*COS(theta) )*SIN(zeta)
!  spp%vars%X(:,2) = ( spp%Ro + r*COS(theta) )*COS(zeta)
!  spp%vars%X(:,3) = spp%Zo + r*SIN(theta)

  Y = r*SIN(theta)
  X = r*COS(theta) + spp%shear_factor*Y

  rotation_angle = 0.5_rp*C_PI - ATAN(1.0_rp,1.0_rp + spp%shear_factor);

  X1 = X*COS(rotation_angle) - Y*SIN(rotation_angle) + spp%Ro
  Y1 = X*SIN(rotation_angle) + Y*COS(rotation_angle) + spp%Zo

  spp%vars%X(:,1) = X1*SIN(zeta)
  spp%vars%X(:,2) = X1*COS(zeta)
  spp%vars%X(:,3) = Y1

  DEALLOCATE(X1)
  DEALLOCATE(Y1)
  DEALLOCATE(X)
  DEALLOCATE(Y)
  DEALLOCATE(rotation_angle)
  DEALLOCATE(theta)
  DEALLOCATE(zeta)
  DEALLOCATE(r)
end subroutine gaussian_elliptic_torus