dommaschk_equilibrium_m Module

[*] W. Dommaschk, "Representations for vacuum potentials in stellarators", Computer Physics Communications 40, pg. 203 (1986)

Definition of Dommaschk potentials [*]. Fully 3D equilibrium


Used by


Interfaces

interface

  • public module subroutine read_bndry_polygons(self, filename, variable, phi_array, polygon_vertices)

    Reads in boundary / exclusion polygon data from NetCDF

    Arguments

    Type IntentOptional Attributes Name
    class(dommaschk_t), intent(in) :: self

    Instance of the type

    character(len=*), intent(in) :: filename

    NetCDF filename

    character(len=*), intent(in) :: variable

    NetCDF variable name

    real(kind=FP), dimension(:), allocatable :: phi_array

    Toroidal angles of each polygon

    real(kind=FP), intent(out), dimension(:,:,:), allocatable :: polygon_vertices

    Closed polygon vertices at each toroidal angle

interface

  • public module subroutine read_rho_polygons(self, filename)

    Reads in flux surface polygon data from NetCDF

    Arguments

    Type IntentOptional Attributes Name
    class(dommaschk_t), intent(inout) :: self

    Instance of the type

    character(len=*), intent(in) :: filename

    NetCDF filename


Derived Types

type, public, extends(equilibrium_t) ::  dommaschk_t

Type implementing 3D vacuum fields as described by Dommaschk [*]. These are determined with toroidal mode numbers m, poloidal mode numbers l, the number of field periods, and fitting coefficients which are specific to each magnetic configuration.

Components

Type Visibility Attributes Name Initial
logical, public :: initialized = .false.
real(kind=FP), public :: x0

Magnetic axis x = R/R0 (in normalised units)

real(kind=FP), public :: y0

Magnetic axis y = Z/R0 (in normalised units)

real(kind=FP), public :: phi0 = 0.0_FP

Magnetic axis phi

real(kind=FP), public :: xmin

Box limits

real(kind=FP), public :: xmax

Box limits

real(kind=FP), public :: ymin

Box limits

real(kind=FP), public :: ymax

Box limits

real(kind=FP), public :: rhomax

Global limits for rho (rho = normalised psi, n.b. there may also be region-specific limits defined in equi)

real(kind=FP), public :: rhomin

Global limits for rho (rho = normalised psi, n.b. there may also be region-specific limits defined in equi)

real(kind=FP), public, dimension(:,:,:), allocatable :: CD_r_coef

Coefficients of the R terms of the C^D_{m,k} function. See Eqs. 31 and 32 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: CN_r_coef

Coefficients of the R terms of the C^N_{m,k} function. See Eqs. 31 and 32 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: C_r_power

Powers of the R terms of the C^D_{m,k} and C^N_{m,k} functions. See Eqs. 31 and 32 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: CD_lnr_coef

Coefficients of the log(R) terms of the C^D_{m,k} function. See Eqs. 31 and 32 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: CN_lnr_coef

Coefficients of the log(R) terms of the C^N_{m,k} function. See Eqs. 31 and 32 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: C_lnr_power

Powers of the log(R) terms of the C^D_{m,k} and C^N_{m,k} functions. See Eqs. 31 and 32 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: dCD_dR_r_coef

Coefficients of the R terms of the derivative with respect to R of the C^D_{m,k} function

real(kind=FP), public, dimension(:,:,:), allocatable :: dCN_dR_r_coef

Coefficients of the R terms of the derivative with respect to R of the C^N_{m,k} function

real(kind=FP), public, dimension(:,:,:), allocatable :: dC_dR_r_power

Powers of the R terms of the derivatives with respect to R of the C^D_{m,k} and C^N_{m,k} functions. See Eqs. 31 and 32 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: dCD_dR_lnr_coef

Coefficients of the log(R) terms of the derivative with respect to R of the C^D_{m,k} function

real(kind=FP), public, dimension(:,:,:), allocatable :: dCN_dR_lnr_coef

Coefficients of the log(R) terms of the derivative with respect to R of the C^N_{m,k} function

real(kind=FP), public, dimension(:,:,:), allocatable :: dC_dR_lnr_power

Powers of the log(R) terms of the derivatives with respect to R of the C^D_{m,k} and C^N_{m,k} functions

real(kind=FP), public, dimension(:,:,:), allocatable :: I_mn_coef

Coefficients of the Z terms of the I_{m,n} function. See Eqs. 3, 8, and 9 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: I_mn_power

Powers of the Z terms of the I_{m,n} function. See Eqs. 3, 8, and 9 in [*]

real(kind=FP), public, dimension(:,:,:), allocatable :: dI_dZ_coef

Coefficients of the Z terms of the derivative with respect to Z of the I_{m,n} function

real(kind=FP), public, dimension(:,:,:), allocatable :: dI_dZ_power

Powers of the Z terms of the derivative with respect to Z of the I_{m,n} function.

Type-Bound Procedures

procedure, public, pass(self) :: absb
procedure, public, pass(self) :: bpol
procedure, public :: get_l_pol
procedure, public :: get_m_tor_consecutive
procedure, public :: get_num_field_periods
procedure, public :: init
procedure, public :: display
procedure, public :: debug
procedure, public :: is_axisymmetric
procedure, public :: rho
procedure, public :: bx
procedure, public :: by
procedure, public :: btor
procedure, public :: jacobian
procedure, public :: epol
procedure, public :: erad
procedure, public :: district
procedure, public :: in_vessel
procedure, public :: mag_axis_loc

Functions

public pure function get_l_pol(self)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self

Return Value integer

public pure function get_m_tor_consecutive(self)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self

Return Value integer

public pure function get_num_field_periods(self)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self

Return Value integer

public function is_axisymmetric(self)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self

Return Value logical

public function rho(self, x, y, phi)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi

Return Value real(kind=fp)

public function bx(self, x, y, phi)

Evaluates the radial component of the vacuum magnetic field B according to B_R = dV/dR

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi

Return Value real(kind=fp)

public function by(self, x, y, phi)

Evaluates the radial component of the vacuum magnetic field B according to B_Z = dV/dZ

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi

Return Value real(kind=fp)

public function btor(self, x, y, phi)

Evaluates the poloidal component of the vacuum magnetic field B according to B_phi = 1/R dV/dphi

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi

Return Value real(kind=fp)

public function jacobian(self, x, y, phi)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi

Return Value real(kind=fp)

public function district(self, x, y, phi)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi

Return Value integer

public function in_vessel(self, x, y, phi)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi

Return Value logical


Subroutines

public subroutine init(self, filename)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(inout) :: self
character(len=*), intent(in), optional :: filename

public subroutine check_fitting_coef(self)

Check fitting_coef for consistency. The first condition (from Eq. 12 in [*]) is strict, while the second and third (from Eq. 13a) only enforce stellarator symmetry, which can be violated. Hence, only a warning is provided there.

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(inout) :: self

public subroutine init_CD_CN(self)

Compute and store C^D_{m,k}(R) and C^N_{m,k}(R) (Eq. 31 and 32)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(inout) :: self

public subroutine init_Imn(self)

Compute and store D_{m,n} and N_{m,n} (as used in Eq. 12 in [*]) via Eq. 3

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(inout) :: self

public subroutine init_B_norm(self)

Determine the magnetic field normalization with the un-normalized value of btor evaluated at the location of the magnetic axis. This is used to normalize all subsequent magnetic field calculations.

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(inout) :: self

public subroutine init_rho_array(self)

Calculates the value of rho for every surface in the given rho file. Used later in rho calculation, to interpolate between surfaces

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(inout) :: self

public subroutine init_mag_axis_loc(self)

Initializes two arrays (equidistant in phi) of x- and y-coordinates of magnetic axis within the first field period calculated via field line tracing. These are used as data points for fast interpolation in 'mag_axis_loc'

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(inout) :: self

Instance of class

public subroutine display(self)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self

public subroutine debug(self)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self

public subroutine epol(self, x, y, phi, epolx, epoly)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi
real(kind=FP), intent(out) :: epolx
real(kind=FP), intent(out) :: epoly

public subroutine erad(self, x, y, phi, eradx, erady)

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self
real(kind=FP), intent(in) :: x
real(kind=FP), intent(in) :: y
real(kind=FP), intent(in) :: phi
real(kind=FP), intent(out) :: eradx
real(kind=FP), intent(out) :: erady

public subroutine mag_axis_loc(self, phi, axis_x, axis_y)

Returns the coordinates of magnetic axis

Arguments

Type IntentOptional Attributes Name
class(dommaschk_t), intent(in) :: self

Instance of class

real(kind=FP), intent(in) :: phi

Toroidal angle

real(kind=FP), intent(out) :: axis_x

x-coordinate of the magnetic axis

real(kind=FP), intent(out) :: axis_y

y-coordinate of the magnetic axis