dommaschk_t Derived Type

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

  • private function absb(self, x, y, phi)

    Absolute value of magnetic field.

    Arguments

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

    3D position (x and y normalized)

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

    3D position (x and y normalized)

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

    3D position (x and y normalized)

    Return Value real(kind=fp)

procedure, public, pass(self) :: bpol

  • private function bpol(self, x, y, phi)

    Magnetic field component b poloidal normalised to absolute value of B (on axis)

    Arguments

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

    3D position (x and y normalized)

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

    3D position (x and y normalized)

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

    3D position (x and y normalized)

    Return Value real(kind=fp)

procedure, public :: get_l_pol

  • public pure function get_l_pol(self)

    Arguments

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

    Return Value integer

procedure, public :: get_m_tor_consecutive

procedure, public :: get_num_field_periods

procedure, public :: init

  • public subroutine init(self, filename)

    Arguments

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

procedure, public :: display

  • public subroutine display(self)

    Arguments

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

procedure, public :: debug

  • public subroutine debug(self)

    Arguments

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

procedure, public :: is_axisymmetric

  • public function is_axisymmetric(self)

    Arguments

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

    Return Value logical

procedure, public :: rho

  • 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)

procedure, public :: bx

  • 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)

procedure, public :: by

  • 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)

procedure, public :: btor

  • 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)

procedure, public :: jacobian

  • 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)

procedure, public :: epol

  • 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

procedure, public :: erad

  • 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

procedure, public :: district

  • 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

procedure, public :: in_vessel

  • 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

procedure, public :: mag_axis_loc

  • 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