korc_collisions Module



Contents


Variables

TypeVisibility AttributesNameInitial
character(len=*), private, parameter:: MODEL1 ='SINGLE_SPECIES'
character(len=*), private, parameter:: MODEL2 ='MULTIPLE_SPECIES'
real(kind=rp), private, parameter:: infinity =HUGE(1.0_rp)
type(PARAMS_MS), private :: cparams_ms
type(PARAMS_SS), private :: cparams_ss

Derived Types

type, private :: PARAMS_MS

Components

TypeVisibility AttributesNameInitial
integer, public :: num_impurity_species
real(kind=rp), public :: Te
real(kind=rp), public :: ne
real(kind=rp), public :: nH
real(kind=rp), public :: nef
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: neb
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: Zi
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: Zo
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: Zj
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: nz
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: IZj
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: aZj
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: Ee_IZj
real(kind=rp), public :: rD
real(kind=rp), public :: re
real(kind=rp), public, DIMENSION(11):: aNe =(/111._rp, 100._rp, 90._rp, 80._rp, 71._rp, 62._rp, 52._rp, 40._rp, 24._rp, 23._rp, 0._rp/)
real(kind=rp), public, DIMENSION(19):: aAr =(/96._rp, 90._rp, 84._rp, 78._rp, 72._rp, 65._rp, 59._rp, 53._rp, 47._rp, 44._rp, 41._rp, 38._rp, 25._rp, 32._rp, 27._rp, 21._rp, 13._rp, 13._rp, 0._rp/)
real(kind=rp), public, DIMENSION(11):: INe =(/137.2_rp, 165.2_rp, 196.9_rp, 235.2_rp, 282.8_rp, 352.6_rp, 475.0_rp, 696.8_rp, 1409.2_rp, 1498.4_rp, huge(1._rp)/)
real(kind=rp), public, DIMENSION(19):: IAr =(/188.5_rp, 219.4_rp, 253.8_rp, 293.4_rp, 339.1_rp, 394.5_rp, 463.4_rp, 568.0_rp, 728.0_rp, 795.9_rp, 879.8_rp, 989.9_rp, 1138.1_rp, 1369.5_rp, 1791.2_rp, 2497.0_rp, 4677.2_rp, 4838.2_rp, huge(1._rp)/)

type, private :: PARAMS_SS

Components

TypeVisibility AttributesNameInitial
real(kind=rp), public :: Te
real(kind=rp), public :: Ti
real(kind=rp), public :: ne
real(kind=rp), public :: Zeff
real(kind=rp), public :: rD
real(kind=rp), public :: re
real(kind=rp), public :: CoulombLogee
real(kind=rp), public :: CoulombLogei
real(kind=rp), public :: CLog1
real(kind=rp), public :: CLog2
real(kind=rp), public :: CLog0_1
real(kind=rp), public :: CLog0_2
real(kind=rp), public :: VTe
real(kind=rp), public :: VTeo
real(kind=rp), public :: delta
real(kind=rp), public :: deltao
real(kind=rp), public :: Gammac
real(kind=rp), public :: Gammaco
real(kind=rp), public :: Tau
real(kind=rp), public :: Tauc
real(kind=rp), public :: taur
real(kind=rp), public :: Ec
real(kind=rp), public :: ED
real(kind=rp), public :: dTau
integer(kind=ip), public :: subcycling_iterations
real(kind=rp), public, DIMENSION(3):: x =(/1.0_rp, 0.0_rp, 0.0_rp/)
real(kind=rp), public, DIMENSION(3):: y =(/0.0_rp, 1.0_rp, 0.0_rp/)
real(kind=rp), public, DIMENSION(3):: z =(/0.0_rp, 0.0_rp, 1.0_rp/)
type(PROFILES), public :: P
real(kind=rp), public, DIMENSION(:,:), ALLOCATABLE:: rnd_num
integer, public :: rnd_num_count
integer, public :: rnd_dim =40000000_idef

Functions

private function VTe_wu(Te)

Arguments

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

In Joules

Return Value real(kind=rp)

private function VTe(Te)

Dimensionless temperature

Arguments

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

Return Value real(kind=rp)

private function Gammac_wu(params, ne, Te)

With units

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: ne
real(kind=rp), intent(in) :: Te

Return Value real(kind=rp)

private function Gammacee(v, ne, Te)

Dimensionless ne and Te

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: v
real(kind=rp), intent(in) :: ne
real(kind=rp), intent(in) :: Te

Return Value real(kind=rp)

private function CLog_wu(ne, Te)

With units

Arguments

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

ne is in m^-3 and below is converted to cm^-3

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

Return Value real(kind=rp)

public function CLog0_wu(ne, Te)

With units

Arguments

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

ne is in m^-3 and below is converted to cm^-3

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

Return Value real(kind=rp)

public function CLogee_wu(params, ne, Te)

With units

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: ne

ne is in m^-3 and below is converted to cm^-3

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

Return Value real(kind=rp)

public function CLogei_wu(params, ne, Te)

With units

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: ne

ne is in m^-3 and below is converted to cm^-3

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

Return Value real(kind=rp)

private function CLog(ne, Te)

Arguments

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

Return Value real(kind=rp)

public function CLog0(ne, Te)

Arguments

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

Return Value real(kind=rp)

public function CLogee(v, ne, Te)

Arguments

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

ne is in m^-3 and below is converted to cm^-3

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

Return Value real(kind=rp)

public function CLogei(v, ne, Te)

Arguments

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

ne is in m^-3 and below is converted to cm^-3

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

Return Value real(kind=rp)

private function delta(Te)

Arguments

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

Return Value real(kind=rp)

public function psi(x)

Arguments

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

Return Value real(kind=rp)

private function CA(v)

Arguments

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

Return Value real(kind=rp)

private function CA_SD(v, ne, Te)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: v
real(kind=rp), intent(in) :: ne
real(kind=rp), intent(in) :: Te

Return Value real(kind=rp)

public function dCA_SD(v, me, ne, Te)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: v
real(kind=rp), intent(in) :: me
real(kind=rp), intent(in) :: ne
real(kind=rp), intent(in) :: Te

Return Value real(kind=rp)

private function CF(params, v)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: v

Return Value real(kind=rp)

private function CF_SD(params, v, ne, Te)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: v
real(kind=rp), intent(in) :: ne
real(kind=rp), intent(in) :: Te

Return Value real(kind=rp)

private function CB_ee(v)

Arguments

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

Return Value real(kind=rp)

private function CB_ei(params, v)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: v

Return Value real(kind=rp)

private function CB_ee_SD(v, ne, Te, Zeff)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: v
real(kind=rp), intent(in) :: ne
real(kind=rp), intent(in) :: Te
real(kind=rp), intent(in) :: Zeff

Return Value real(kind=rp)

private function CB_ei_SD(params, v, ne, Te, Zeff)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: v
real(kind=rp), intent(in) :: ne
real(kind=rp), intent(in) :: Te
real(kind=rp), intent(in) :: Zeff

Return Value real(kind=rp)

private function nu_S(params, v)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: v

Return Value real(kind=rp)

public function h_j(i, v)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: i
real(kind=rp), intent(in) :: v

Return Value real(kind=rp)

public function g_j(i, v)

Arguments

Type IntentOptional AttributesName
integer, intent(in) :: i
real(kind=rp), intent(in) :: v

Return Value real(kind=rp)

private function nu_D(params, v)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(in) :: v

Return Value real(kind=rp)

private function nu_par(v)

Arguments

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

Return Value real(kind=rp)

private function fun(v)

Arguments

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

Return Value real(kind=rp)

private function cross(a, b)

Arguments

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

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


Subroutines

private subroutine load_params_ms(params)

Arguments

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

private subroutine load_params_ss(params)

Arguments

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

public subroutine initialize_collision_params(params)

Arguments

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

private subroutine normalize_params_ms(params)

Arguments

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

private subroutine normalize_params_ss(params)

Calculate constant quantities used in various functions within this module

Arguments

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

public subroutine normalize_collisions_params(params)

Arguments

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

public subroutine collision_force(spp, U, Fcoll)

For multiple-species collisions J. R. Martin-Solis et al. PoP 22, 092512 (2015) if (params%collisions .AND. (TRIM(params%collisions_model) .EQ. 'MULTIPLE_SPECIES')) then call collision_force(spp(ii),U_os,Fcoll) U_RC = U_RC + a*Fcoll/spp(ii)%q end if

Arguments

Type IntentOptional AttributesName
type(SPECIES), intent(in) :: spp
real(kind=rp), intent(in), DIMENSION(3):: U
real(kind=rp), intent(out), DIMENSION(3):: Fcoll

public subroutine define_collisions_time_step(params)

Arguments

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

private subroutine unitVectorsC(B, b1, b2, b3)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in), DIMENSION(3):: B
real(kind=rp), intent(out), DIMENSION(3):: b1
real(kind=rp), intent(out), DIMENSION(3):: b2
real(kind=rp), intent(out), DIMENSION(3):: b3

private subroutine unitVectors_p(b_unit_X, b_unit_Y, b_unit_Z, b1_X, b1_Y, b1_Z, b2_X, b2_Y, b2_Z, b3_X, b3_Y, b3_Z)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in), DIMENSION(8):: b_unit_X
real(kind=rp), intent(in), DIMENSION(8):: b_unit_Y
real(kind=rp), intent(in), DIMENSION(8):: b_unit_Z
real(kind=rp), intent(out), DIMENSION(8):: b1_X
real(kind=rp), intent(out), DIMENSION(8):: b1_Y
real(kind=rp), intent(out), DIMENSION(8):: b1_Z
real(kind=rp), intent(out), DIMENSION(8):: b2_X
real(kind=rp), intent(out), DIMENSION(8):: b2_Y
real(kind=rp), intent(out), DIMENSION(8):: b2_Z
real(kind=rp), intent(out), DIMENSION(8):: b3_X
real(kind=rp), intent(out), DIMENSION(8):: b3_Y
real(kind=rp), intent(out), DIMENSION(8):: b3_Z

public subroutine check_collisions_params(spp)

Arguments

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

public subroutine include_CoulombCollisions_FO_p(tt, params, X_X, X_Y, X_Z, U_X, U_Y, U_Z, B_X, B_Y, B_Z, me, P, F, flag, PSIp)

This subroutine performs a Stochastic collision process consistent with the Fokker-Planck model for relativitic electron colliding with a thermal (Maxwellian) plasma. The collision operator is in spherical coordinates of the form found in Papp et al., NF (2011). CA corresponds to the parallel (speed diffusion) process, CF corresponds to a slowing down (momentum loss) process, and CB corresponds to a perpendicular diffusion process. Ordering of the processes are and only the dominant terms are kept.

Arguments

Type IntentOptional AttributesName
integer(kind=ip), intent(in) :: tt
type(KORC_PARAMS), intent(in) :: params
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):: U_X
real(kind=rp), intent(inout), DIMENSION(8):: U_Y
real(kind=rp), intent(inout), DIMENSION(8):: U_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) :: me
type(PROFILES), intent(in) :: P
type(FIELDS), intent(in) :: F
integer(kind=is), intent(inout), DIMENSION(8):: flag
real(kind=rp), intent(in), DIMENSION(8):: PSIp

public subroutine include_CoulombCollisions_GC_p(tt, params, Y_R, Y_PHI, Y_Z, Ppll, Pmu, me, flag, F, P, E_PHI, ne, PSIp)

Arguments

Type IntentOptional AttributesName
integer(kind=ip), intent(in) :: tt
type(KORC_PARAMS), intent(inout) :: params
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):: Ppll
real(kind=rp), intent(inout), DIMENSION(8):: Pmu
real(kind=rp), intent(in) :: me
integer(kind=is), intent(inout), DIMENSION(8):: flag
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(out), DIMENSION(8):: PSIp

private subroutine save_params_ms(params)

Arguments

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

private subroutine save_params_ss(params)

Arguments

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

public subroutine save_collision_params(params)

Arguments

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

private subroutine deallocate_params_ms()

Arguments

None

public subroutine deallocate_collisions_params(params)

Arguments

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