korc_ppusher Module



Contents


Variables

TypeVisibility AttributesNameInitial
real(kind=rp), private :: E0

Dimensionless vacuum permittivity , see korc_units.


Functions

private pure function cross(a, b)

Read more…

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in), DIMENSION(3):: a

Vector .

real(kind=rp), intent(in), DIMENSION(3):: b

Vector .

Return Value real(kind=rp), DIMENSION(3)

Value of

public function deg2rad(x)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: x

Return Value real(kind=rp)

public function rad2deg(x)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: x

Return Value real(kind=rp)


Subroutines

public subroutine initialize_particle_pusher(params)

Read more…

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params

Core KORC simulation parameters.

private subroutine radiation_force_p(q_cache, m_cache, U_X, U_Y, U_Z, E_X, E_Y, E_Z, B_X, B_Y, B_Z, Frad_X, Frad_Y, Frad_Z)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
real(kind=rp), intent(in), DIMENSION(8):: U_X

, where is the particle's velocity.

real(kind=rp), intent(in), DIMENSION(8):: U_Y

, where is the particle's velocity.

real(kind=rp), intent(in), DIMENSION(8):: U_Z

, where is the particle's velocity.

real(kind=rp), intent(in), DIMENSION(8):: E_X

Electric field seen by each particle. This is given in Cartesian coordinates.

real(kind=rp), intent(in), DIMENSION(8):: E_Y

Electric field seen by each particle. This is given in Cartesian coordinates.

real(kind=rp), intent(in), DIMENSION(8):: E_Z

Electric field seen by each particle. This is given in Cartesian coordinates.

real(kind=rp), intent(in), DIMENSION(8):: B_X

Magnetic field seen by each particle. This is given in Cartesian coordinates.

real(kind=rp), intent(in), DIMENSION(8):: B_Y

Magnetic field seen by each particle. This is given in Cartesian coordinates.

real(kind=rp), intent(in), DIMENSION(8):: B_Z

Magnetic field seen by each particle. This is given in Cartesian coordinates.

real(kind=rp), intent(out), DIMENSION(8):: Frad_X

The calculated synchrotron radiation reaction force .

real(kind=rp), intent(out), DIMENSION(8):: Frad_Y

The calculated synchrotron radiation reaction force .

real(kind=rp), intent(out), DIMENSION(8):: Frad_Z

The calculated synchrotron radiation reaction force .

public subroutine FO_init(params, F, spp, output, step)

Calls get_fields in korc_fields.

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params

Core KORC simulation parameters.

type(FIELDS), intent(in) :: F

An instance of the KORC derived type FIELDS.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

logical, intent(in) :: output
logical, intent(in) :: step

public subroutine adv_FOeqn_top(params, F, P, spp)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(FIELDS), intent(in) :: F

An instance of the KORC derived type FIELDS.

type(PROFILES), intent(in) :: P

An instance of the KORC derived type PROFILES.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

public subroutine advance_FOeqn_vars(tt, a, q_cache, m_cache, params, X_X, X_Y, X_Z, V_X, V_Y, V_Z, B_X, B_Y, B_Z, E_X, E_Y, E_Z, P, F, g, flag_cache, PSIp)

Calls radiation_force in korc_ppusher.

Arguments

Type IntentOptional AttributesName
integer(kind=ip), intent(in) :: tt

Time step used in the leapfrog step ().

real(kind=rp), intent(in) :: a

This variable is used to simplify notation in the code, and is given by ,

real(kind=rp), intent(in) :: q_cache

Time step used in the leapfrog step ().

real(kind=rp), intent(in) :: m_cache

Time step used in the leapfrog step ().

type(KORC_PARAMS), intent(in) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: X_X
real(kind=rp), intent(inout), DIMENSION(8):: X_Y
real(kind=rp), intent(inout), DIMENSION(8):: X_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_X
real(kind=rp), intent(inout), DIMENSION(8):: V_Y
real(kind=rp), intent(inout), DIMENSION(8):: V_Z
real(kind=rp), intent(in), DIMENSION(8):: B_X
real(kind=rp), intent(in), DIMENSION(8):: B_Y
real(kind=rp), intent(in), DIMENSION(8):: B_Z
real(kind=rp), intent(in), DIMENSION(8):: E_X
real(kind=rp), intent(in), DIMENSION(8):: E_Y
real(kind=rp), intent(in), DIMENSION(8):: E_Z
type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F
real(kind=rp), intent(inout), DIMENSION(8):: g
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
real(kind=rp), intent(in), DIMENSION(8):: PSIp

public subroutine advance_FP3Deqn_vars(params, X_X, X_Y, X_Z, V_X, V_Y, V_Z, g, m_cache, B0, lam, R0, q0, EF0, B_X, B_Y, B_Z, E_X, E_Y, E_Z, P, F, flag_cache, PSIp)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(in), DIMENSION(8):: X_X
real(kind=rp), intent(in), DIMENSION(8):: X_Y
real(kind=rp), intent(in), DIMENSION(8):: X_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_X
real(kind=rp), intent(inout), DIMENSION(8):: V_Y
real(kind=rp), intent(inout), DIMENSION(8):: V_Z
real(kind=rp), intent(inout), DIMENSION(8):: g
real(kind=rp), intent(in) :: m_cache
real(kind=rp), intent(in) :: B0
real(kind=rp), intent(in) :: lam
real(kind=rp), intent(in) :: R0
real(kind=rp), intent(in) :: q0
real(kind=rp), intent(in) :: EF0
real(kind=rp), intent(in), DIMENSION(8):: B_X
real(kind=rp), intent(in), DIMENSION(8):: B_Y
real(kind=rp), intent(in), DIMENSION(8):: B_Z
real(kind=rp), intent(in), DIMENSION(8):: E_X
real(kind=rp), intent(in), DIMENSION(8):: E_Y
real(kind=rp), intent(in), DIMENSION(8):: E_Z
type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
real(kind=rp), intent(in), DIMENSION(8):: PSIp

public subroutine adv_FOinterp_top(params, F, P, spp)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(FIELDS), intent(in) :: F

An instance of the KORC derived type FIELDS.

type(PROFILES), intent(in) :: P

An instance of the KORC derived type PROFILES.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

public subroutine advance_FOinterp_vars(tt, a, q_cache, m_cache, params, X_X, X_Y, X_Z, V_X, V_Y, V_Z, B_X, B_Y, B_Z, E_X, E_Y, E_Z, g, flag_cache, P, F, PSIp)

Calls radiation_force in korc_ppusher.

Arguments

Type IntentOptional AttributesName
integer(kind=ip), intent(in) :: tt

Time step used in the leapfrog step ().

real(kind=rp), intent(in) :: a

This variable is used to simplify notation in the code, and is given by ,

real(kind=rp), intent(in) :: q_cache

Time step used in the leapfrog step ().

real(kind=rp), intent(in) :: m_cache

Time step used in the leapfrog step ().

type(KORC_PARAMS), intent(in) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: X_X
real(kind=rp), intent(inout), DIMENSION(8):: X_Y
real(kind=rp), intent(inout), DIMENSION(8):: X_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_X
real(kind=rp), intent(inout), DIMENSION(8):: V_Y
real(kind=rp), intent(inout), DIMENSION(8):: V_Z
real(kind=rp), intent(in), DIMENSION(8):: B_X
real(kind=rp), intent(in), DIMENSION(8):: B_Y
real(kind=rp), intent(in), DIMENSION(8):: B_Z
real(kind=rp), intent(in), DIMENSION(8):: E_X
real(kind=rp), intent(in), DIMENSION(8):: E_Y
real(kind=rp), intent(in), DIMENSION(8):: E_Z
real(kind=rp), intent(inout), DIMENSION(8):: g
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F
real(kind=rp), intent(in), DIMENSION(8):: PSIp

public subroutine advance_FP3Dinterp_vars(params, X_X, X_Y, X_Z, V_X, V_Y, V_Z, g, m_cache, B_X, B_Y, B_Z, E_X, E_Y, E_Z, flag_cache, P, F, PSIp)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(in), DIMENSION(8):: X_X
real(kind=rp), intent(in), DIMENSION(8):: X_Y
real(kind=rp), intent(in), DIMENSION(8):: X_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_X
real(kind=rp), intent(inout), DIMENSION(8):: V_Y
real(kind=rp), intent(inout), DIMENSION(8):: V_Z
real(kind=rp), intent(inout), DIMENSION(8):: g
real(kind=rp), intent(in) :: m_cache
real(kind=rp), intent(in), DIMENSION(8):: B_X
real(kind=rp), intent(in), DIMENSION(8):: B_Y
real(kind=rp), intent(in), DIMENSION(8):: B_Z
real(kind=rp), intent(in), DIMENSION(8):: E_X
real(kind=rp), intent(in), DIMENSION(8):: E_Y
real(kind=rp), intent(in), DIMENSION(8):: E_Z
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F
real(kind=rp), intent(in), DIMENSION(8):: PSIp

public subroutine GC_init(params, F, spp)

Read more…

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(FIELDS), intent(inout) :: F

An instance of the KORC derived type FIELDS.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

public subroutine adv_GCeqn_top(params, F, P, spp)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(FIELDS), intent(inout) :: F

An instance of the KORC derived type FIELDS.

type(PROFILES), intent(in) :: P

An instance of the KORC derived type PROFILES.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

public subroutine advance_GCeqn_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, flag_cache, q_cache, m_cache, B_R, B_PHI, B_Z, F, P, PSIp, E_PHI)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
integer(kind=is), intent(inout), dimension(8):: flag_cache
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
type(FIELDS), intent(in) :: F

An instance of the KORC derived type PROFILES.

type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: PSIp
real(kind=rp), intent(out), DIMENSION(8):: E_PHI

public subroutine advance_FPeqn_vars(params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, flag_cache, m_cache, F, P, PSIp)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
real(kind=rp), intent(in) :: m_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(inout), DIMENSION(8):: PSIp

public subroutine adv_GCinterp_psi_top_FS(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(inout) :: F

public subroutine adv_GCinterp_psi_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(inout) :: F

public subroutine adv_GCinterp_psiwE_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(inout) :: F

public subroutine adv_GCinterp_psi2x1t_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(inout) :: F

public subroutine adv_GCinterp_B_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F

public subroutine adv_GCinterp_B2D_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F

public subroutine adv_GCinterp_2DBdB_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F

public subroutine adv_GCinterp_3DBdB1_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F

public subroutine adv_GCinterp_3DBdB_top(params, spp, P, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

type(SPECIES), intent(inout), DIMENSION(:), ALLOCATABLE:: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F

public subroutine advance_GCinterp_psi_vars_FS(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, PSIp, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: PSIp
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z

public subroutine advance_GCinterp_psi_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, PSIp, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, ne)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: PSIp
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(out), DIMENSION(8):: ne

public subroutine advance_GCinterp_psiwE_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, PSIp, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, ne)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: PSIp
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(out), DIMENSION(8):: ne

public subroutine advance_GCinterp_psi2x1t_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, PSIp, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, ne)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: PSIp
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(out), DIMENSION(8):: ne

public subroutine advance_GCinterp_B2D_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, PSIp)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(inout), DIMENSION(8):: PSIp

public subroutine advance_GCinterp_2DBdB_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, PSIp)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(out), DIMENSION(8):: PSIp

public subroutine advance_GCinterp_3DBdB_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, PSIp)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(inout), DIMENSION(8):: PSIp

public subroutine advance_GCinterp_3DBdB1_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, PSIp)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(out), DIMENSION(8):: PSIp

public subroutine advance_GCinterp_B_vars(vars, pp, tt, params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, q_cache, m_cache, flag_cache, F, P, B_R, B_PHI, B_Z, E_PHI, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, PSIp)

Read more…

Arguments

Type IntentOptional AttributesName
type(PARTICLES), intent(inout) :: vars
integer, intent(in) :: pp
integer(kind=ip), intent(in) :: tt

time iterator.

type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(inout), DIMENSION(8):: Y_R
real(kind=rp), intent(inout), DIMENSION(8):: Y_PHI
real(kind=rp), intent(inout), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: B_R
real(kind=rp), intent(out), DIMENSION(8):: B_PHI
real(kind=rp), intent(out), DIMENSION(8):: B_Z
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_R
real(kind=rp), intent(out), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(out), DIMENSION(8):: curlb_Z
real(kind=rp), intent(out), DIMENSION(8):: gradB_R
real(kind=rp), intent(out), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(out), DIMENSION(8):: gradB_Z
real(kind=rp), intent(inout), DIMENSION(8):: PSIp

public subroutine advance_FPinterp_vars(params, Y_R, Y_PHI, Y_Z, V_PLL, V_MU, m_cache, flag_cache, F, P, E_PHI, ne, PSIp)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(in), DIMENSION(8):: Y_R
real(kind=rp), intent(in), DIMENSION(8):: Y_PHI
real(kind=rp), intent(in), DIMENSION(8):: Y_Z
real(kind=rp), intent(inout), DIMENSION(8):: V_PLL
real(kind=rp), intent(inout), DIMENSION(8):: V_MU
real(kind=rp), intent(in) :: m_cache
integer(kind=is), intent(inout), DIMENSION(8):: flag_cache
type(FIELDS), intent(in) :: F
type(PROFILES), intent(in) :: P
real(kind=rp), intent(out), DIMENSION(8):: E_PHI
real(kind=rp), intent(out), DIMENSION(8):: ne
real(kind=rp), intent(inout), DIMENSION(8):: PSIp

private subroutine GCEoM_p(params, RHS_R, RHS_PHI, RHS_Z, RHS_PLL, B_R, B_PHI, B_Z, E_R, E_PHI, E_Z, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, V_PLL, V_MU, Y_R, q_cache, m_cache)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(out), DIMENSION(8):: RHS_R
real(kind=rp), intent(out), DIMENSION(8):: RHS_PHI
real(kind=rp), intent(out), DIMENSION(8):: RHS_Z
real(kind=rp), intent(out), DIMENSION(8):: RHS_PLL
real(kind=rp), intent(in), DIMENSION(8):: B_R
real(kind=rp), intent(in), DIMENSION(8):: B_PHI
real(kind=rp), intent(in), DIMENSION(8):: B_Z
real(kind=rp), intent(in), DIMENSION(8):: E_R
real(kind=rp), intent(in), DIMENSION(8):: E_PHI
real(kind=rp), intent(in), DIMENSION(8):: E_Z
real(kind=rp), intent(in), DIMENSION(8):: curlb_R
real(kind=rp), intent(in), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(in), DIMENSION(8):: curlb_Z
real(kind=rp), intent(in), DIMENSION(8):: gradB_R
real(kind=rp), intent(in), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(in), DIMENSION(8):: gradB_Z
real(kind=rp), intent(in), DIMENSION(8):: V_PLL
real(kind=rp), intent(in), DIMENSION(8):: V_MU
real(kind=rp), intent(in), DIMENSION(8):: Y_R
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache

private subroutine GCEoM1_p(tt, P, F, params, RHS_R, RHS_PHI, RHS_Z, RHS_PLL, RHS_MU, B_R, B_PHI, B_Z, E_R, E_PHI, E_Z, curlb_R, curlb_PHI, curlb_Z, gradB_R, gradB_PHI, gradB_Z, V_PLL, V_MU, Y_R, Y_Z, q_cache, m_cache, PSIp, ne)

Arguments

Type IntentOptional AttributesName
integer(kind=ip), intent(in) :: tt
type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F
type(KORC_PARAMS), intent(inout) :: params

Core KORC simulation parameters.

real(kind=rp), intent(out), DIMENSION(8):: RHS_R
real(kind=rp), intent(out), DIMENSION(8):: RHS_PHI
real(kind=rp), intent(out), DIMENSION(8):: RHS_Z
real(kind=rp), intent(out), DIMENSION(8):: RHS_PLL
real(kind=rp), intent(out), DIMENSION(8):: RHS_MU
real(kind=rp), intent(in), DIMENSION(8):: B_R
real(kind=rp), intent(in), DIMENSION(8):: B_PHI
real(kind=rp), intent(in), DIMENSION(8):: B_Z
real(kind=rp), intent(in), DIMENSION(8):: E_R
real(kind=rp), intent(in), DIMENSION(8):: E_PHI
real(kind=rp), intent(in), DIMENSION(8):: E_Z
real(kind=rp), intent(in), DIMENSION(8):: curlb_R
real(kind=rp), intent(in), DIMENSION(8):: curlb_PHI
real(kind=rp), intent(in), DIMENSION(8):: curlb_Z
real(kind=rp), intent(in), DIMENSION(8):: gradB_R
real(kind=rp), intent(in), DIMENSION(8):: gradB_PHI
real(kind=rp), intent(in), DIMENSION(8):: gradB_Z
real(kind=rp), intent(in), DIMENSION(8):: V_PLL
real(kind=rp), intent(in), DIMENSION(8):: V_MU
real(kind=rp), intent(in), DIMENSION(8):: Y_R
real(kind=rp), intent(in), DIMENSION(8):: Y_Z
real(kind=rp), intent(in) :: q_cache
real(kind=rp), intent(in) :: m_cache
real(kind=rp), intent(in), DIMENSION(8):: PSIp
real(kind=rp), intent(out), DIMENSION(8):: ne

private subroutine aux_fields(pp, spp, gradB, curlb, Bmag)

Arguments

Type IntentOptional AttributesName
integer :: pp
type(SPECIES), intent(in) :: spp

An instance of the derived type SPECIES containing all the parameters and simulation variables of the different species in the simulation.

real(kind=rp), intent(inout), DIMENSION(3):: gradB
real(kind=rp), intent(inout), DIMENSION(3):: curlb
real(kind=rp), intent(in) :: Bmag