kt_grids_box_config_type Derived Type

type, public, extends(abstract_config_type) :: kt_grids_box_config_type

Used to represent the input configuration of kt_grids_box


Contents


Components

Type Visibility Attributes Name Initial
logical, public :: exist = .false.

Does the related namelist exist in the target input file?

integer, public :: index = 0

Used to hold the specific index of numbered namelists

logical, public :: skip_read = .false.

Do we want to skip the read step in init?

logical, public :: skip_broadcast = .false.

Do we want to skip the broadcast step in init?

logical, public :: gryfx = .false.

integer, public :: jtwist = 1

For finite magnetic shear determines the box size in the x direction according to . This also affects the number of connections at each ky when linked boundary conditions are selected in the dist_fn_knobs namelist.

This gets a smart default Initialised to jtwist = max(int(2*pi*shat+0.5,1)) so that . If the magnetic shear is less than around 0.16 then jtwist will default to the minimum allowed value of 1.

real, public :: ly = 0.0

Sets the box size in the y direction. If set to 0 (the default) then we set ly=2*pi*y0.

integer, public :: n0 = 0

If set greater than zero (the default) then this sets the toroidal mode number of the first non-zero ky by overriding the value given for y0 through y0 = 1.0/(n0*rhostar_box*drhodpsi) where drhodpsi is determined during geometry setup.

integer, public :: naky = 0

The actual number of ky modes. For nonlinear runs it is generally recommended to use ny instead. If set to 0 (the default) this will be automatically set to 1 + (ny-1)/3. If both ny and naky are set then GS2 will check that ny is sufficiently high to ensure de-aliasing. It can be larger than this minimum value. Setting both values can be useful to allow values to be selected which are performant for the FFTs and provide a good range of sweetspots.

integer, public :: ntheta0 = 0

The actual number of theta0 modes. For nonlinear runs it is generally recommended to use nx instead. If set to 0 (the default) this will be automatically set to 1 + 2*(nx-1)/3. If both nx and ntheta0 are set then GS2 will check that nx is sufficiently high to ensure de-aliasing. It can be larger than this minimum value. Setting both values can be useful to allow values to be selected which are performant for the FFTs and provide a good range of sweetspots.

integer, public :: nx = 0

The number of kx points in inputs to the fft routines, and hence the number of radial points used in real space calculations. This differs from the actual number of kx points simulated in the rest of the code due to the need to prevent aliasing. The number of kx modes actually simulated (ntheta0) is, by default, equal to 1 + 2*(nx - 1)/3.

integer, public :: ny = 0

The number of ky points in inputs to the fft routines, and hence the number of binormal points used in real space calculations. This differs from the actual number of ky points simulated in the rest of the code due to the need to prevent aliasing. The number of ky modes actually simulated (naky) is, by default, equal to 1 + (ny - 1)/3.

real, public :: rhostar_box = 0.0

The rhostar (rhoref/Lref) to use. Only used if n0 also set greater than zero. If rhostar_box and n0 are greater than zero then y0=1.0/(n0*rhostar_box*drhodpsi), which effectively sets the minimum non-zero ky used in the simulation.

real, public :: rtwist = 0.0

Expert usage only -- more documentation required.

Used to control the kx spacing in simulations with effectively zero shear () where linked boundaries are not appropriate so periodic boundaries are used. Also only used if x0 has been set to zero (the default). If rtwist is set to 0.0 (the default) then it is set to the value of jtwist. Effectively ends up setting the box size in the x direction, as if rtwist > 0 and if rtwist < 0. See x0 for an alternative.

real, public :: x0 = 0.

Controls the box length in the x direction (measured in the reference Larmour radius) if the magnetic shear is small (). The box size in the x direction is given by . See rtwist for an alternative.

real, public :: y0 = 2.0

Controls the box length in the y direction (measured in the reference Larmour radius). The box size in the y direction is given by . Note if y0 is set negative then, it is replaced with -1/y0 and Effectively sets the minimum wavelength captured by the box.


Type-Bound Procedures

procedure, public, :: is_initialised => is_initialised_generic

procedure, public, :: init => init_generic

  • private subroutine init_generic(self, name, requires_index, index)

    Fully initialise the config object

    Arguments

    Type IntentOptional Attributes Name
    class(abstract_config_type), intent(inout) :: self
    character(len=*), intent(in), optional :: name
    logical, intent(in), optional :: requires_index
    integer, intent(in), optional :: index

procedure, public, :: setup => setup_generic

  • private subroutine setup_generic(self, name, requires_index, index)

    Do some standard setup/checking

    Arguments

    Type IntentOptional Attributes Name
    class(abstract_config_type), intent(inout) :: self
    character(len=*), intent(in), optional :: name
    logical, intent(in), optional :: requires_index
    integer, intent(in), optional :: index

procedure, public, :: write_namelist_header

  • private subroutine write_namelist_header(self, unit)

    Write the namelist header for this instance

    Arguments

    Type IntentOptional Attributes Name
    class(abstract_config_type), intent(in) :: self
    integer, intent(in) :: unit

procedure, public, :: get_name => get_name_generic

  • private function get_name_generic(self)

    Returns the namelist name. Not very useful at the moment but may want to do more interesting things in the future

    Arguments

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

    Return Value character(len=CONFIG_MAX_NAME_LEN)

procedure, public, :: get_requires_index => get_requires_index_generic

  • private function get_requires_index_generic(self)

    Returns the requires_index value. Allows access whilst keeping the variable private

    Arguments

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

    Return Value logical

procedure, public, nopass :: write_namelist_footer

  • private subroutine write_namelist_footer(unit)

    Write the namelist footer

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: unit
  • private subroutine write_key_val_string(key, val, unit)

    Writes a {key,val} pair where the value is of type character

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    character(len=*), intent(in) :: val
    integer, intent(in) :: unit
  • private subroutine write_key_val_real(key, val, unit)

    Writes a {key,val} pair where the value is of type real

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    real, intent(in) :: val
    integer, intent(in) :: unit
  • private subroutine write_key_val_complex(key, val, unit)

    Writes a {key,val} pair where the value is of type complex

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    complex, intent(in) :: val
    integer, intent(in) :: unit
  • private subroutine write_key_val_integer(key, val, unit)

    Writes a {key,val} pair where the value is of type integer

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    integer, intent(in) :: val
    integer, intent(in) :: unit
  • private subroutine write_key_val_logical(key, val, unit)

    Writes a {key,val} pair where the value is of type logical

    Arguments

    Type IntentOptional Attributes Name
    character(len=*), intent(in) :: key
    logical, intent(in) :: val
    integer, intent(in) :: unit
  • private subroutine write_key_val_real_array(self, key, val, unit)

    Writes a {key,val} pair where the value is of type real array

    Arguments

    Type IntentOptional Attributes Name
    class(abstract_config_type), intent(in) :: self
    character(len=*), intent(in) :: key
    real, intent(in), dimension(:) :: val
    integer, intent(in) :: unit
  • private subroutine write_key_val_complex_array(self, key, val, unit)

    Writes a {key,val} pair where the value is of type complex array

    Arguments

    Type IntentOptional Attributes Name
    class(abstract_config_type), intent(in) :: self
    character(len=*), intent(in) :: key
    complex, intent(in), dimension(:) :: val
    integer, intent(in) :: unit
  • private subroutine write_key_val_integer_array(self, key, val, unit)

    Writes a {key,val} pair where the value is of type integer array

    Arguments

    Type IntentOptional Attributes Name
    class(abstract_config_type), intent(in) :: self
    character(len=*), intent(in) :: key
    integer, intent(in), dimension(:) :: val
    integer, intent(in) :: unit

procedure, public :: read => read_kt_grids_box_config

procedure, public :: write => write_kt_grids_box_config

  • private subroutine write_kt_grids_box_config(self, unit)

    Writes out a namelist representing the current state of the config object

    Arguments

    Type IntentOptional Attributes Name
    class(kt_grids_box_config_type), intent(in) :: self
    integer, intent(in), optional :: unit

procedure, public :: reset => reset_kt_grids_box_config

procedure, public :: broadcast => broadcast_kt_grids_box_config

procedure, public, nopass :: get_default_name => get_default_name_kt_grids_box_config

procedure, public, nopass :: get_default_requires_index => get_default_requires_index_kt_grids_box_config

Source Code

  type, extends(abstract_config_type) :: kt_grids_box_config_type
     ! namelist : kt_grids_box_parameters
     ! indexed : false
     !> FIXME: Add documentation
     !>
     !> @note We should probably remove/move this flag to some gryfx
     !> specific location.
     logical :: gryfx = .false.
     !> For finite magnetic shear determines the box size in the x
     !> direction according to \(L_x = L_y
     !> \textrm{jtwist}/2\pi\hat{s}\).  This also affects the number
     !> of connections at each `ky` when linked boundary conditions
     !> are selected in the [[dist_fn_knobs]] namelist.
     !>
     !> This gets a smart default Initialised to `jtwist =
     !> max(int(2*pi*shat+0.5,1))` so that \(L_x\approx L_y\). If the
     !> magnetic shear is less than around 0.16 then `jtwist` will
     !> default to the minimum allowed value of 1.
     integer :: jtwist = 1
     !> Sets the box size in the y direction. If set to 0 (the default) then
     !> we set `ly=2*pi*y0`.
     real :: ly = 0.0
     !> If set greater than zero (the default) then this sets the
     !> toroidal mode number of the first non-zero `ky` by overriding
     !> the value given for `y0` through `y0 =
     !> 1.0/(n0*rhostar_box*drhodpsi)` where `drhodpsi` is determined
     !> during geometry setup.
     integer :: n0 = 0
     !> The actual number of ky modes. For nonlinear runs it is
     !> generally recommended to use `ny` instead. If set to 0 (the
     !> default) this will be automatically set to `1 + (ny-1)/3`.  If
     !> both `ny` and `naky` are set then GS2 will check that `ny`
     !> is sufficiently high to ensure de-aliasing. It can be larger
     !> than this minimum value. Setting both values can be useful to
     !> allow values to be selected which are performant for the FFTs
     !> and provide a good range of sweetspots.
     integer :: naky = 0
     !> The actual number of theta0 modes. For nonlinear runs it is
     !> generally recommended to use `nx` instead. If set to 0 (the
     !> default) this will be automatically set to `1 + 2*(nx-1)/3`.
     !> If both `nx` and `ntheta0` are set then GS2 will check that
     !> `nx` is sufficiently high to ensure de-aliasing. It can be
     !> larger than this minimum value. Setting both values can be
     !> useful to allow values to be selected which are performant for
     !> the FFTs and provide a good range of sweetspots.
     integer :: ntheta0 = 0
     !> The number of kx points in inputs to the fft routines, and
     !> hence the number of radial points used in real space
     !> calculations. This differs from the actual number of kx points
     !> simulated in the rest of the code due to the need to prevent
     !> aliasing. The number of kx modes actually simulated
     !> (`ntheta0`) is, by default, equal to `1 + 2*(nx - 1)/3`.
     integer :: nx = 0
     !> The number of ky points in inputs to the fft routines, and
     !> hence the number of binormal points used in real space
     !> calculations. This differs from the actual number of ky points
     !> simulated in the rest of the code due to the need to prevent
     !> aliasing. The number of ky modes actually simulated
     !> (`naky`) is, by default, equal to `1 + (ny - 1)/3`.
     integer :: ny = 0
     !> The rhostar (`rhoref/Lref`) to use. Only used if `n0` also set
     !> greater than zero.  If `rhostar_box` and `n0` are greater than
     !> zero then `y0=1.0/(n0*rhostar_box*drhodpsi)`, which
     !> effectively sets the minimum non-zero `ky` used in the
     !> simulation.
     real :: rhostar_box = 0.0
     !> Expert usage only -- more documentation required.
     !>
     !> Used to control the kx spacing in simulations with effectively
     !> zero shear (\(\< 10^{-5}\)) where linked boundaries are not
     !> appropriate so periodic boundaries are used. Also only used if
     !> `x0` has been set to zero (the default). If `rtwist` is set to
     !> 0.0 (the default) then it is set to the value of
     !> `jtwist`. Effectively ends up setting the box size in the x
     !> direction, as \(L_x = L_y \textrm{rtwist}\) if `rtwist > 0 `
     !> and \(L_x = L_y / \textrm{rtwist}\) if `rtwist < 0`. See
     !> [[kt_grids_box_parameters:x0]] for an alternative.
     real :: rtwist = 0.0
     !> Controls the box length in the x direction (measured in the
     !> reference Larmour radius) if the magnetic shear is small (\(\<
     !> 10^{-5}\)). The box size in the x direction is given by \(L_x
     !> = 2\pi x_0\). See [[kt_grids_box_parameters:rtwist]] for an
     !> alternative.
     real :: x0 = 0.
     !> Controls the box length in the y direction (measured in the
     !> reference Larmour radius). The box size in the y direction is
     !> given by \(L_y = 2\pi y_0\). Note if `y0` is set negative
     !> then, it is replaced with `-1/y0` and Effectively sets the
     !> minimum wavelength captured by the box.
     real :: y0 = 2.0
   contains
     procedure, public :: read => read_kt_grids_box_config
     procedure, public :: write => write_kt_grids_box_config
     procedure, public :: reset => reset_kt_grids_box_config
     procedure, public :: broadcast => broadcast_kt_grids_box_config
     procedure, public, nopass :: get_default_name => get_default_name_kt_grids_box_config
     procedure, public, nopass :: get_default_requires_index => get_default_requires_index_kt_grids_box_config
  end type kt_grids_box_config_type