Subroutine that calculates characteristic scales of the current KORC simulation.
Normalization and non-dimensionalization of the variables and equations of motion allows us to solve them more accurately by reducing truncation erros when performing operations that combine small and large numbers.
For normalizing and obtaining the non-dimensional form of the variables and equations solved in KORC we use characteristic scales calculated with the input data of each KORC simulation.
Characteristic scale | Symbol | Value | Description |
---|---|---|---|
Velocity | Speed of light | ||
Time | Inverse of electron cyclotron frequency | ||
Relativistic time | Inverse of relativistic electron cyclotron frequency | ||
Length | -- | ||
Mass | Electron mass | ||
Charge | Absolute value of electron charge | ||
Momentum | -- | ||
Magnetic field | Magnetic field at the magnetic axis | ||
Electric field | -- | ||
Energy | -- | ||
Temperature | Temperature given in Joules. | ||
Density | -- | ||
Magnetic moment | -- | ||
Pressure | -- | -- |
where , , , , , and .
Characteristic pressure needs to be defined.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
type(KORC_PARAMS), | intent(inout) | :: | params | Core KORC simulation parameters. |
||
type(SPECIES), | intent(inout), | DIMENSION(:), ALLOCATABLE | :: | spp | An instance of KORC's derived type SPECIES containing all the information of different electron species. See korc_types. |
|
type(FIELDS), | intent(in) | :: | F | An instance of KORC's derived type FIELDS containing all the information about the fields used in the simulation. See korc_types and korc_fields. |
subroutine compute_charcs_plasma_params(params,spp,F)
!! @note Subroutine that calculates characteristic scales of
!! the current KORC simulation. @endnote
!! Normalization and non-dimensionalization of the variables and equations
!! of motion allows us to solve them more accurately by reducing truncation
!! erros when performing operations that combine small and large numbers.
!!
!! For normalizing and obtaining the non-dimensional form of the variables
!! and equations solved in KORC we use characteristic scales calculated with
!! the input data of each KORC simulation.
!! <table cellspacing="10">
!! <caption id="multi_row">Characteristic scales in KORC</caption>
!! <tr><th>Characteristic scale</th> <th>Symbol</th> <th>Value</th> <th>Description</th></tr>
!! <tr><td rowspan="1">Velocity <td>\(v_{ch}\) <td>\(c\) <td> Speed of light
!! <tr><td rowspan="1">Time <td>\(t_{ch}\) <td>\(\Omega^{-1} = m_{ch}/q_{ch}B_{ch}\) <td> Inverse of electron cyclotron frequency
!! <tr><td rowspan="1">Relativistic time <td>\(t_{r,ch}\) <td>\(\Omega_r^{-1} = \gamma m_{ch}/q_{ch}B_{ch}\) <td> Inverse of relativistic electron cyclotron frequency
!! <tr><td rowspan="1">Length <td>\(l_{ch}\) <td>\(v_{ch}t_{ch}\) <td>--
!! <tr><td rowspan="1">Mass <td>\(m_{ch}\) <td>\(m_e\) <td> Electron mass
!! <tr><td rowspan="1">Charge <td>\(q_{ch}\) <td>\(e\) <td> Absolute value of electron charge
!! <tr><td rowspan="1">Momentum <td>\(p_{ch}\) <td>\(m_{ch}v_{ch}\) <td> --
!! <tr><td rowspan="1">Magnetic field <td>\(B_{ch}\) <td>\(B_0\) <td> Magnetic field at the magnetic axis
!! <tr><td rowspan="1">Electric field <td>\(E_{ch}\) <td>\(v_{ch}B_{ch}\) <td> --
!! <tr><td rowspan="1">Energy <td>\(\mathcal{E}_{ch}\)<td>\(m_{ch}v_{ch}^2\) <td>--
!! <tr><td rowspan="1">Temperature <td>\(T_{ch}\) <td>\(m_{ch}v_{ch}^2\) <td> Temperature given in Joules.
!! <tr><td rowspan="1">Density <td>\(n_{ch}\) <td>\(l_{ch}^{-3}\) <td>--
!! <tr><td rowspan="1">Magnetic moment <td>\(\mu_{ch}\)<td>\(m_{ch}v_{ch}^2/B_{ch}\) <td>--
!! <tr><td rowspan="1">Pressure <td>\(P_{ch}\) <td>-- <td>--
!! </table>
!! With these characteristic scales we can write the dimensionless
!! form of all the equations. For example, the Lorentz force for a
!! charged particle \(q\), mass \(m\), and momentum
!! \(\mathbf{p}=\gamma m \mathbf{v}\) can be written as:
!!
!! $$\frac{d \mathbf{p}'}{dt'} = q'\left[ \mathbf{E}' +
!! \frac{\mathbf{p}'}{\gamma m'}\times \mathbf{B}' \right],$$
!!
!! where \(\mathbf{p}' = \mathbf{p}/p_{ch}\), \(t' = t/t_{ch}\),
!! \(q' = q/q_{ch}\), \(m' = m/m_{ch}\), \(\mathbf{E}' = \mathbf{E}/E_{ch}\),
!! and \(\mathbf{B}'=\mathbf{B}/B_{ch}\).
!! @todo Characteristic pressure needs to be defined.
TYPE(KORC_PARAMS), INTENT(INOUT) :: params
!! Core KORC simulation parameters.
TYPE(SPECIES), DIMENSION(:), ALLOCATABLE, INTENT(INOUT) :: spp
!! An instance of KORC's derived type SPECIES containing all the
!! information of different electron species. See [[korc_types]].
TYPE(FIELDS), INTENT(IN) :: F
!! An instance of KORC's derived type FIELDS containing all the
!! information about the fields used in the simulation.
!! See [[korc_types]] and [[korc_fields]].
INTEGER :: ii
!! Index of the spp array containing the mass, electric charge
!! and corresponding cyclotron frequency used to derived some characteristic scales.
params%cpp%velocity = C_C
params%cpp%Bo = ABS(F%Bo)
params%cpp%Eo = ABS(params%cpp%velocity*params%cpp%Bo)
! Non-relativistic cyclotron frequency
spp(:)%wc = ( ABS(spp(:)%q)/spp(:)%m )*params%cpp%Bo
! Relativistic cyclotron frequency
spp(:)%wc_r = ABS(spp(:)%q)*params%cpp%Bo/( spp(:)%go*spp(:)%m )
ii = MAXLOC(spp(:)%wc,1) ! Index to maximum cyclotron frequency
params%cpp%time = 1.0_rp/spp(ii)%wc
ii = MAXLOC(spp(:)%wc_r,1) ! Index to maximum relativistic cyclotron frequency
params%cpp%time_r = 1.0_rp/spp(ii)%wc_r
params%cpp%mass = C_ME
params%cpp%charge = C_E
params%cpp%length = params%cpp%velocity*params%cpp%time
params%cpp%energy = params%cpp%mass*params%cpp%velocity**2
params%cpp%density = 1.0_rp/params%cpp%length**3
params%cpp%pressure = 0.0_rp
params%cpp%temperature = params%cpp%energy
end subroutine compute_charcs_plasma_params