PROFILES Derived Type

type, public :: PROFILES

KORC can run using either analytical and pre-computed plasma profiles. Pre-computed plasma profiles, as in the case of pre-computed electric or magnetic fields, are interpolated to electrons' position in korc_profiles.

There are two types of analytical plsama profiles that can be used in KORC: 3rd degree polynomial radial plasma profiles, and radial plasma profiles with a dependency: where is a given plasma parameter at the magnetic axis, and is the plasma radius as measured from the magnetic axis to the last closed flux surface. Notice that the larger is, the more uniform the radial profiles are.


Inherits

type~~profiles~~InheritsGraph type~profiles PROFILES type~mesh MESH type~profiles->type~mesh X

Contents

Source Code


Components

TypeVisibility AttributesNameInitial
type(MESH), public :: X

An instance of the KORC derived data type MESH.

real(kind=rp), public :: a

Plasma radius as measured from the magnetic axis

real(kind=rp), public :: R0
real(kind=rp), public :: Z0
real(kind=rp), public :: R0_RE
real(kind=rp), public :: Z0_RE
integer, public, DIMENSION(3):: dims

Dimensions of the arrays containing the pre-computed profiles data. dims=(number of grid nodes along , number of grid nodes along , number of grid nodes along ).

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 :: n_ne

used in of the electron density profile.

real(kind=rp), public :: n_Te

used in of the electron temperature profile.

real(kind=rp), public :: n_Zeff

used in of the profile.

real(kind=rp), public :: n_REr0 =0._rp
real(kind=rp), public :: n_tauion =0._rp
real(kind=rp), public :: n_tauin =0._rp
real(kind=rp), public :: n_tauout =0._rp
real(kind=rp), public :: n_shelfdelay =0._rp
real(kind=rp), public :: n_lamfront =0._rp
real(kind=rp), public :: n_lamback =0._rp
real(kind=rp), public :: n_lamshelf =0._rp
real(kind=rp), public :: n_shelf =0._rp
real(kind=rp), public :: psiN_0 =1._rp
real(kind=rp), public, DIMENSION(4):: a_ne

Coefficients of the polynomial electron density profile. See detailed description above, a_ne=(,,,).

real(kind=rp), public, DIMENSION(4):: a_Te

Coefficients of the polynomial electron temperature profile. See detailed description above, a_ne=(,,,).

real(kind=rp), public, DIMENSION(4):: a_Zeff

Coefficients of the profile. See detailed description above, a_ne=(,,,).

character(len=MAX_STRING_LENGTH), public :: Zeff_profile

String containing the type of profile to be used in the simulation.

real(kind=rp), public :: Zeffo

at the magnetic axis.

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

3-D array for keeping the pre-computed data of the profile.

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

2-D array for keeping the pre-computed data of the profile.

character(len=MAX_STRING_LENGTH), public :: ne_profile

String containing the type of electron density profile to be used in the simulation.

real(kind=rp), public :: neo

Electron density at the magnetic axis

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

3-D array for keeping the pre-computed data of the electron density profile.

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

2-D array for keeping the pre-computed data of the electron density profile.

character(len=MAX_STRING_LENGTH), public :: Te_profile

String containing the type of electron temperature profile to be used in the simulation.

real(kind=rp), public :: Teo

Electron temperature at the magnetic axis

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

3-D array for keeping the pre-computed data of the electron density profile.

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

2-D array for keeping the pre-computed data of the electron density profile.

character(len=MAX_STRING_LENGTH), public :: filename

Full path to the HDF5 file containing the pre-computed plasma profiles.

logical, public :: axisymmetric

Flag to indicate if the plasma profiles are axisymmetric.

real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: RHON
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: nRE_2D
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: nAr0_2D
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: nAr1_2D
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: nAr2_2D
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: nAr3_2D
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: nD_2D
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: nD1_2D
integer(kind=C_INT), public :: FIO_ne
integer(kind=C_INT), public :: FIO_ni
integer(kind=C_INT), public :: FIO_te
integer(kind=C_INT), public, DIMENSION(:), ALLOCATABLE:: FIO_nimp
integer(kind=C_INT), public :: FIO_zeff

Source Code

  TYPE, PUBLIC :: PROFILES
     !! @note KORC derived data type having information about the plasma
     !! profiles. 
     !! See [[korc_profiles.f90("file")]] for more information. @endnote
     !! KORC can run using either analytical and pre-computed plasma profiles. 
     !! Pre-computed plasma profiles, 
     !! as in the case of pre-computed electric or magnetic fields, are
     !! interpolated 
     !! to electrons' position in [[korc_profiles]].
     !!
     !! There are two types of analytical plsama profiles that can be used
     !! in KORC: 
     !! 3rd degree polynomial radial plasma profiles,
     !! $$f(r) = a_3r^3 + a_2r^2 +a_1r + a_0,$$
     !! and radial plasma profiles with a \(\tanh(r)\) dependency:
     !! $$f(r) = f_0\left[1 - \tanh^n\left(\frac{2r}{a}\right)\right],$$
     !! where \(f_0\) is a given plasma parameter at the magnetic axis,
     !! and \(a\) is 
     !! the plasma radius as measured 
     !! from the magnetic axis to the last closed flux surface. Notice that the 
     !! larger \(n\) is, the more uniform the radial profiles are.

     TYPE(MESH) 				        :: X 
     !! An instance of the KORC derived data type MESH.
     REAL(rp) 				        :: a 
     !! Plasma radius as measured from the magnetic axis
     REAL(rp) 				        :: R0
     REAL(rp) 				        :: Z0

     REAL(rp) 				        :: R0_RE
     REAL(rp) 				        :: Z0_RE
     
     INTEGER, DIMENSION(3) 			:: dims 
     !! Dimensions of the arrays containing the pre-computed profiles data. dims=(number of grid nodes along \(R\), 
     !! number of grid nodes along \(\phi\), number of grid nodes along \(Z\)).
     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) 					:: n_ne 
     !! \(n\) used in \(\tanh^n(r)\) of the electron density profile.
     REAL(rp) 					:: n_Te 
     !! \(n\) used in \(\tanh^n(r)\) of the electron temperature profile.
     REAL(rp) 					:: n_Zeff 
     !! \(n\) used in \(\tanh^n(r)\) of the \(Z_{eff}\) profile.

     REAL(rp)  ::  n_REr0=0._rp
     REAL(rp)  ::  n_tauion=0._rp
     REAL(rp)  ::  n_tauin=0._rp
     REAL(rp)  ::  n_tauout=0._rp
     REAL(rp)  ::  n_shelfdelay=0._rp
     REAL(rp)  ::  n_lamfront=0._rp
     REAL(rp)  ::  n_lamback=0._rp
     REAL(rp)  ::  n_lamshelf=0._rp
     REAL(rp)  ::  n_shelf=0._rp
     REAL(rp)  ::  psiN_0=1._rp

     
     REAL(rp), DIMENSION(4) 			:: a_ne 
     !! Coefficients of the polynomial electron density profile. 
     !! See detailed description above, a_ne=(\(a_{0}\),\(a_{2}\),\(a_{3}\),\(a_{4}\)).
     REAL(rp), DIMENSION(4) 			:: a_Te 
     !! Coefficients of the polynomial electron temperature profile. 
     !! See detailed description above, a_ne=(\(a_{0}\),\(a_{2}\),\(a_{3}\),\(a_{4}\)).
     REAL(rp), DIMENSION(4) 			:: a_Zeff 
     !! Coefficients of the \(Z_{eff}\) profile. 
     !! See detailed description above, a_ne=(\(a_{0}\),\(a_{2}\),\(a_{3}\),\(a_{4}\)).

     ! Zeff
     CHARACTER(MAX_STRING_LENGTH) 		:: Zeff_profile 
     !! String containing the type of \(Z_{eff}\) profile to be used in the simulation.
     REAL(rp) 					:: Zeffo 
     !! \(Z_{eff}\) at the magnetic axis.
     REAL(rp), DIMENSION(:,:,:), ALLOCATABLE      :: Zeff_3D 
     !! 3-D array for keeping the pre-computed data of the \(Z_{eff}\) profile.
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: Zeff_2D 
     !! 2-D array for keeping the pre-computed data of the \(Z_{eff}\) profile.

     ! Density
     CHARACTER(MAX_STRING_LENGTH) 		:: ne_profile 
     !! String containing the type of electron density profile to be used in the simulation.
     REAL(rp) 					:: neo 
     !! Electron density at the magnetic axis
     REAL(rp), DIMENSION(:,:,:), ALLOCATABLE      :: ne_3D 
     !! 3-D array for keeping the pre-computed data of the electron density profile.
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: ne_2D 
     !! 2-D array for keeping the pre-computed data of the electron density profile.

     !Temperature
     CHARACTER(MAX_STRING_LENGTH) 		:: Te_profile 
     !! String containing the type of electron temperature profile to be used in the simulation.
     REAL(rp) 					:: Teo 
     !! Electron temperature at the magnetic axis
     REAL(rp), DIMENSION(:,:,:), ALLOCATABLE      :: Te_3D 
     !! 3-D array for keeping the pre-computed data of the electron density profile.
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: Te_2D 
     !! 2-D array for keeping the pre-computed data of the electron density profile.

     CHARACTER(MAX_STRING_LENGTH) 		:: filename 
     !! Full path to the HDF5 file containing the pre-computed plasma profiles.
     LOGICAL 					:: axisymmetric 
     !! Flag to indicate if the plasma profiles are axisymmetric.
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: RHON
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: nRE_2D
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: nAr0_2D
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: nAr1_2D
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: nAr2_2D
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: nAr3_2D
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: nD_2D
     REAL(rp), DIMENSION(:,:), ALLOCATABLE 	:: nD1_2D 
     
#ifdef FIO
     INTEGER (C_INT)                         :: FIO_ne
     INTEGER (C_INT)                         :: FIO_ni
     INTEGER (C_INT)                         :: FIO_te
     INTEGER (C_INT), DIMENSION(:), ALLOCATABLE  :: FIO_nimp
     INTEGER (C_INT)                         :: FIO_zeff
#endif
  END TYPE PROFILES