korc_experimental_pdf Module



Contents


Variables

TypeVisibility AttributesNameInitial
type(PARAMS), private :: pdf_params
type(HOLLMANN_PARAMS), private :: h_params
real(kind=rp), private, parameter:: xo =(C_ME*C_C**2/C_E)/1.0E6
real(kind=rp), private, parameter:: Tol =1.0E-5_rp
real(kind=rp), private, parameter:: minmax_buffer_size =10.0_rp

Derived Types

type, private :: PARAMS

Components

TypeVisibility AttributesNameInitial
real(kind=rp), public :: E
real(kind=rp), public :: Zeff
real(kind=rp), public :: max_pitch_angle
real(kind=rp), public :: min_pitch_angle
real(kind=rp), public :: min_energy
real(kind=rp), public :: max_energy
real(kind=rp), public :: min_p
real(kind=rp), public :: max_p
real(kind=rp), public :: k
real(kind=rp), public :: t
real(kind=rp), public :: fGo
real(kind=rp), public :: Bo
real(kind=rp), public :: lambda
real(kind=rp), public :: A_fact

type, private :: HOLLMANN_PARAMS

Components

TypeVisibility AttributesNameInitial
character(len=MAX_STRING_LENGTH), public :: filename
real(kind=rp), public :: E
real(kind=rp), public :: Eo
real(kind=rp), public :: sigma_E
real(kind=rp), public :: Zeff
real(kind=rp), public :: sigma_Z
real(kind=rp), public :: max_pitch_angle
real(kind=rp), public :: min_pitch_angle
real(kind=rp), public :: min_sampling_energy
real(kind=rp), public :: max_sampling_energy
real(kind=rp), public :: min_sampling_g
real(kind=rp), public :: max_sampling_g
real(kind=rp), public :: min_energy
real(kind=rp), public :: max_energy
real(kind=rp), public :: min_g
real(kind=rp), public :: max_g
real(kind=rp), public :: min_pitch
real(kind=rp), public :: max_pitch
integer, public :: N
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: E_axis
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: g
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: fRE_E
real(kind=rp), public, DIMENSION(:), ALLOCATABLE:: fRE_pitch
character(len=MAX_STRING_LENGTH), public :: current_direction
real(kind=rp), public :: Bo
real(kind=rp), public :: lambda
real(kind=rp), public :: A_fact

Functions

private function deg2rad(x)

Arguments

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

Return Value real(kind=rp)

private function rad2deg(x)

Arguments

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

Return Value real(kind=rp)

private function fGamma(x, k, t)

Arguments

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

Return Value real(kind=rp)

private function fRE(eta, p)

Arguments

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

Return Value real(kind=rp)

private function fRExPR(eta, p)

Arguments

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

Return Value real(kind=rp)

private function random_norm(mean, sigma)

Arguments

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

Return Value real(kind=rp)

private function IntK(v, x)

Arguments

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

Return Value real(kind=rp)

public function besselk(v, x)

Arguments

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

Return Value real(kind=rp)

private function IntGamma(a, b, k, t)

@brief Extended trapezoidal rule for integrating the Gamma PDF. See Sec. 4.2 of Numerical Recipies in Fortran 77.

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: a
real(kind=rp), intent(in) :: b
real(kind=rp), intent(in) :: k
real(kind=rp), intent(in) :: t

Return Value real(kind=rp)

private function IntBesselK(a, b)

@brief Extended trapezoidal rule for integrating the modified Bessel function of second kind. See Sec. 4.2 of Numerical Recipies in Fortran 77.

Arguments

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

Return Value real(kind=rp)

private function PR(eta, p, Bo, l)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: eta
real(kind=rp), intent(in) :: p
real(kind=rp), intent(in) :: Bo
real(kind=rp), intent(in) :: l

Return Value real(kind=rp)

private function fRE_H(eta, g)

Arguments

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

Return Value real(kind=rp)

public function fRE_H_3D(F, eta, g, R, Z, R0, Z0)

Arguments

Type IntentOptional AttributesName
type(FIELDS), intent(in) :: F
real(kind=rp), intent(in) :: eta
real(kind=rp), intent(in) :: g
real(kind=rp), intent(in) :: R
real(kind=rp), intent(in) :: Z
real(kind=rp), intent(in) :: R0
real(kind=rp), intent(in) :: Z0

Return Value real(kind=rp)

public function fRE_HxPR(eta, g)

Arguments

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

Return Value real(kind=rp)

private function fRE_pitch(g)

Arguments

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

Return Value real(kind=rp)

public function PSI_ROT_exp(R, R0, sigR, Z, Z0, sigZ, theta)

Arguments

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

R-coordinate of MH sampled location

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

R-coordinate of center of 2D Gaussian

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

Variance of first dimension of 2D Gaussian

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

Z-coordinate of MH sampled location

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

Z-coordinate of center of 2D Gaussian

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

Variance of second dimension of 2D Gaussian

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

Angle of counter-clockwise rotation (in radians), of 2D Gaussian distribution relative to R,Z

Return Value real(kind=rp)

Argument of exponential comprising 2D Gaussian distribution

public function indicator_exp(psi, psi_max)

Arguments

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

Return Value real(kind=rp)


Subroutines

public subroutine get_experimentalG_distribution(params, g, eta, go, etao)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(inout), DIMENSION(:), ALLOCATABLE:: g
real(kind=rp), intent(inout), DIMENSION(:), ALLOCATABLE:: eta
real(kind=rp), intent(out) :: go
real(kind=rp), intent(out) :: etao

private subroutine initialize_params(params)

Arguments

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

private subroutine P_integral(z, P)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in) :: z
real(kind=rp), intent(out) :: P

private subroutine sample_distribution(params, g, eta, go, etao)

Read more…

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
real(kind=rp), intent(inout), DIMENSION(:), ALLOCATABLE:: g
real(kind=rp), intent(inout), DIMENSION(:), ALLOCATABLE:: eta
real(kind=rp), intent(out) :: go
real(kind=rp), intent(out) :: etao

public subroutine get_Hollmann_distribution(params, spp)

Arguments

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

public subroutine get_Hollmann_distribution_3D(params, spp, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(in) :: params
type(SPECIES), intent(inout) :: spp
type(FIELDS), intent(in) :: F

public subroutine get_Hollmann_distribution_3D_psi(params, spp, F)

Arguments

Type IntentOptional AttributesName
type(KORC_PARAMS), intent(inout) :: params
type(SPECIES), intent(inout) :: spp
type(FIELDS), intent(in) :: F

public subroutine initialize_Hollmann_params(params)

Arguments

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

public subroutine normalize_Hollmann_params(params)

Arguments

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

public subroutine load_data_from_hdf5()

Arguments

None

public subroutine sample_Hollmann_distribution(params, spp)

MCMC and MH algorithm perfomred on single MPI process to sample distribution function fRE_H

Arguments

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

public subroutine sample_Hollmann_distribution_3D(params, spp, F)

Read more…

Arguments

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

Core KORC simulation parameters.

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

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

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

An instance of the KORC derived type FIELDS.

public subroutine sample_Hollmann_distribution_3D_psi(params, spp, F)

Read more…

Arguments

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

Core KORC simulation parameters.

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

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

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

An instance of the KORC derived type FIELDS.

private subroutine save_params(params)

Arguments

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

public subroutine save_Hollmann_params(params)

Arguments

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