FIELDS Derived Type

type, public :: FIELDS


Contents

Source Code


Components

TypeVisibility AttributesNameInitial
type(A_FIELD), public :: AB

An instance of the KORC derived data type A_FIELD.

type(V_FIELD_3D), public :: E_3D

KORC 3-D vector field of the pre-computed electric field.

type(V_FIELD_3D), public :: B_3D
type(V_FIELD_3D), public :: dBdR_3D
type(V_FIELD_3D), public :: dBdPHI_3D
type(V_FIELD_3D), public :: dBdZ_3D

KORC 3-D vector field of the pre-computed magnetic field.

type(V_FIELD_2D), public :: E_2D

KORC 2-D vector field of the pre-computed electric field.

type(V_FIELD_2D), public :: B_2D
type(V_FIELD_2D), public :: dBdR_2D
type(V_FIELD_2D), public :: dBdPHI_2D
type(V_FIELD_2D), public :: dBdZ_2D

KORC 3-D vector field of the pre-computed magnetic field.

type(V_FIELD_2D), public :: gradB_2D
type(V_FIELD_3D), public :: gradB_3D

KORC 3-D vector field of the gradient of the magnitude of the pre-computed magnetic field.

type(V_FIELD_2D), public :: curlb_2D
type(V_FIELD_3D), public :: curlb_3D

KORC 3-D vector field of the curl of the unit vector in the direction of the pre-computed magnetic field.

type(V_FIELD_1D), public :: E_SC_1D
type(V_FIELD_1D), public :: J0_SC_1D
type(V_FIELD_1D), public :: J1_SC_1D
type(V_FIELD_1D), public :: J2_SC_1D
type(V_FIELD_1D), public :: J3_SC_1D
type(V_FIELD_1D), public :: A1_SC_1D
type(V_FIELD_1D), public :: A2_SC_1D
type(V_FIELD_1D), public :: A3_SC_1D
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: r_1D
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: PSIP_1D
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: dMagPsiSqdPsiP
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: ddMagPsiSqdPsiPSq
type(MESH), public :: X

An instance of the KORC derived type MESH.

character(len=MAX_STRING_LENGTH), public :: E_model

Name for dynamical, analytic, electric field model to be added to

real(kind=rp), public :: E_dyn
real(kind=rp), public :: E_pulse
real(kind=rp), public :: E_width
real(kind=rp), public :: PSIP_min
real(kind=rp), public :: PSIp_lim

interpolated E field

integer, public :: res_double
integer, public, DIMENSION(3):: dims

Dimensions of the KORC vector field. dims=(number of grid nodes along , number of grid nodes along , number of grid nodes along ).

integer, public :: dim_1D
integer, public :: subcycle_E_SC
real(kind=rp), public :: dt_E_SC
real(kind=rp), public :: Ip_exp
real(kind=rp), public :: Ip0
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: PSIp
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: PSIp_FS
real(kind=rp), public, DIMENSION(:,:,:), ALLOCATABLE:: PSIp3D

2-D array for storing the data of the poloidal magnetic flux.

real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: FLAG2D

2-D array defining the simulation domain where pre-computed data exist.

real(kind=rp), public, DIMENSION(:,:,:), ALLOCATABLE:: FLAG3D

3-D array defining the simulation domain where pre-computed data exist.

real(kind=rp), public :: Eo

Characteristic electric field.

real(kind=rp), public :: Bo

Characteristic magnetic field.

real(kind=rp), public :: Ro

Radial position of the magnetic axis.

real(kind=rp), public :: Zo

position of the magnetic axis.

logical, public :: Bfield

Flag to indicate whether a pre-computed magnetic field will be used (Bfield=T) or not (Bfield=F).

logical, public :: dBfield

Flag to indicate whether a pre-computed magnetic field will be used (Bfield=T) or not (Bfield=F).

logical, public :: Bflux
logical, public :: Bflux3D

Flag to indicate whether a pre-computed poloidal magnetic flux will be used (Bflux=T) or not (Bflux=F).

logical, public :: Efield

Flag to indicate whether a pre-computed electric field will be used (Efield=T) or not (Efield=F).

logical, public :: Bfield_in_file

Flag to indicate if a pre-computed magnetic field is in the input file.

logical, public :: dBfield_in_file

Flag to indicate if a pre-computed magnetic field is in the input file.

logical, public :: Bflux_in_file

Flag to indicate if a pre-computed poloidal magnetic flux is in the input file.

logical, public :: Efield_in_file

Flag to indicate if a pre-computed electric field is in the input file.

logical, public :: axisymmetric_fields

Flag to indicate if the pre-computed fields are axisymmetric.

logical, public :: Dim2x1t
logical, public :: E_2x1t
logical, public :: ReInterp_2x1t
real(kind=rp), public :: t0_2x1t
integer, public :: ind0_2x1t
integer, public :: ind_2x1t

Source Code

  TYPE, PUBLIC :: FIELDS
     !! @note Derived type with all the variables and data of analytical 
     !! and pre-computed electric and magnetic fields. @endnote

     TYPE(A_FIELD) 	 			:: AB 
     !! An instance of the KORC derived data type A_FIELD.
     TYPE(V_FIELD_3D) 				:: E_3D 
     !! KORC 3-D vector field of the pre-computed electric field.
     TYPE(V_FIELD_3D) 				:: B_3D
     TYPE(V_FIELD_3D) 				:: dBdR_3D
     TYPE(V_FIELD_3D) 				:: dBdPHI_3D
     TYPE(V_FIELD_3D) 				:: dBdZ_3D 
     !! KORC 3-D vector field of the pre-computed magnetic field.
     TYPE(V_FIELD_2D) 				:: E_2D 
     !! KORC 2-D vector field of the pre-computed electric field.
     TYPE(V_FIELD_2D) 				:: B_2D
     TYPE(V_FIELD_2D) 				:: dBdR_2D
     TYPE(V_FIELD_2D) 				:: dBdPHI_2D
     TYPE(V_FIELD_2D) 				:: dBdZ_2D 
     !! KORC 3-D vector field of the pre-computed magnetic field.
     TYPE(V_FIELD_2D) 				:: gradB_2D
     TYPE(V_FIELD_3D) 				:: gradB_3D 
     !! KORC 3-D vector field of the gradient of the magnitude of the
     !! pre-computed magnetic field.
     TYPE(V_FIELD_2D) 				:: curlb_2D
     TYPE(V_FIELD_3D) 				:: curlb_3D 
     !! KORC 3-D vector field of the curl of the unit vector in the
     !! direction of the pre-computed magnetic field.
     TYPE(V_FIELD_1D) 				:: E_SC_1D
     TYPE(V_FIELD_1D) 				:: J0_SC_1D
     TYPE(V_FIELD_1D) 				:: J1_SC_1D
     TYPE(V_FIELD_1D) 				:: J2_SC_1D
     TYPE(V_FIELD_1D) 				:: J3_SC_1D
     TYPE(V_FIELD_1D) 				:: A1_SC_1D
     TYPE(V_FIELD_1D) 				:: A2_SC_1D
     TYPE(V_FIELD_1D) 				:: A3_SC_1D
     
     REAL(rp), DIMENSION(:), ALLOCATABLE :: r_1D
     REAL(rp), DIMENSION(:), ALLOCATABLE :: PSIP_1D
     REAL(rp), DIMENSION(:), ALLOCATABLE :: dMagPsiSqdPsiP
     REAL(rp), DIMENSION(:), ALLOCATABLE :: ddMagPsiSqdPsiPSq
     TYPE(MESH) 		 		:: X 
     !! An instance of the KORC derived type MESH.
     CHARACTER(MAX_STRING_LENGTH) :: E_model
     !! Name for dynamical, analytic, electric field model to be added to
     REAL(rp)  :: E_dyn
     REAL(rp)  :: E_pulse
     REAL(rp)  :: E_width
     REAL(rp)  :: PSIP_min
     REAL(rp)  :: PSIp_lim
     !! interpolated E field
     INTEGER 			:: res_double
     INTEGER, DIMENSION(3) 			:: dims 
     !! Dimensions of the KORC vector field. dims=(number of grid 
     !! nodes along \(R\), number of grid nodes along \(\phi\), 
     !! number of grid nodes along \(Z\)).
     INTEGER 			:: dim_1D
     INTEGER 			:: subcycle_E_SC
     REAL(rp)  :: dt_E_SC,Ip_exp,Ip0
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: PSIp
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: PSIp_FS
     REAL(rp), DIMENSION(:,:,:), ALLOCATABLE 	:: PSIp3D 
     !! 2-D array for storing the data of the poloidal magnetic flux.
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: FLAG2D 
     !! 2-D array defining the simulation domain where pre-computed data exist.
     REAL(rp), DIMENSION(:,:,:), ALLOCATABLE      :: FLAG3D 
     !! 3-D array defining the simulation domain where pre-computed data exist.
     REAL(rp) 					:: Eo 
     !! Characteristic electric field.
     REAL(rp) 					:: Bo 
     !! Characteristic magnetic field.
     REAL(rp) 					:: Ro 
     !! Radial position of the magnetic axis.
     REAL(rp) 					:: Zo 
     !! \(Z\) position of the magnetic axis.
     LOGICAL 					:: Bfield 
     !! Flag to indicate whether a pre-computed magnetic field will be
     !! used (Bfield=T) or not (Bfield=F).
     LOGICAL 					:: dBfield 
     !! Flag to indicate whether a pre-computed magnetic field will be
     !! used (Bfield=T) or not (Bfield=F).
     LOGICAL 					:: Bflux
     LOGICAL 					:: Bflux3D 
     !! Flag to indicate whether a pre-computed poloidal magnetic flux will
     !! be used (Bflux=T) or not (Bflux=F).
     LOGICAL 					:: Efield 
     !! Flag to indicate whether a pre-computed electric field will be used
     !! (Efield=T) or not (Efield=F).
     LOGICAL 					:: Bfield_in_file 
     !! Flag to indicate if a pre-computed magnetic field is in the input file.
     LOGICAL 					:: dBfield_in_file 
     !! Flag to indicate if a pre-computed magnetic field is in the input file.
     LOGICAL 					:: Bflux_in_file 
     !! Flag to indicate if a pre-computed poloidal magnetic flux is in the
     !! input file.
     LOGICAL 					:: Efield_in_file 
     !! Flag to indicate if a pre-computed electric field is in the input file.
     LOGICAL 					:: axisymmetric_fields 
     !! Flag to indicate if the pre-computed fields are axisymmetric.
     LOGICAL 					:: Dim2x1t
     LOGICAL 					:: E_2x1t,ReInterp_2x1t
     REAL(rp)  :: t0_2x1t
     INTEGER  :: ind0_2x1t,ind_2x1t
  END TYPE FIELDS