geod_schw Derived Type

type, public, extends(ode_equation) :: geod_schw

A class that defines the geodesic evolution equations for a particle moving in a Schwarzschild spacetime.

For this system nvars=7. The quantities stored in var_data are 1: , 2: , 3: , 4: , 5: , 6: , 7: , where is the radial coordinate in Schwarzschild coordinates, is the azimuthal angle, and are the time, radial and components of the 4-velocity, is the mass of the scalar charge and s a variable defined in the osculating orbits framework that varies from to over a full radial cycle. Note that is stricly constant for all other cases than a scalar charge and should stricly not be included in a generic geodesic evolution. Also is included for convenience as it is useful to control the turn on of the back-reaction in terms of timescales related to the radial cycle.


Inherits

type~~geod_schw~~InheritsGraph type~geod_schw geod_schw type~ode_equation ode_equation type~geod_schw->type~ode_equation type~equation equation type~ode_equation->type~equation

Contents

Source Code


Components

TypeVisibility AttributesNameInitial
integer(kind=ip), public :: ntmp

The number of temporary storage variables to allocate.

character(len=:), public, allocatable:: ename

The name of the system of equations

integer(kind=ip), public :: nvars

The number of variables in the ODE system.

real(kind=wp), public, dimension(:), allocatable:: var_data

A 1d array of reals that contains the data variables.

real(kind=wp), public, dimension(:), allocatable:: rhs_data

A 1d array of reals that contains the RHS variables.

real(kind=wp), public, dimension(:,:), allocatable:: tmp_data

A 2d array of reals that contains the temporary variables needed by the time integrator.

integer(kind=ip), public :: io_id

The file unit id used for output for this system of ODE's.

real(kind=wp), public :: En

The orbital energy per unit mass.

real(kind=wp), public :: Lz

The orbital angular momentum per unit mass.

real(kind=wp), public :: e

The orbital eccentricity.

real(kind=wp), public :: p

The orbital semi-latus rectum.

real(kind=wp), public :: w

The value of at periapsis.

real(kind=wp), public :: d2rdt2

The second time derivative of the radial coordinate. Needed for the time dependent coordinate transformation.

real(kind=wp), public, dimension(4):: force

The self-force or any external force .

real(kind=wp), public, dimension(4):: accel

The acceleration .

real(kind=wp), public :: udota

The dot-product of the 4-velocity and the force .


Finalization Procedures

final :: close_geod_schw

The finalizer.


Type-Bound Procedures

procedure, public :: set_to_zero => ode_set_to_zero

The set_to_zero routine is provided by ode_set_to_zero.

  • interface

    public module subroutine ode_set_to_zero(this, dest)

    The interface for the ODE version of set_to_zero. This interface is consistent with eq_set_to_zero_interface.

    Arguments

    Type IntentOptional AttributesName
    class(ode_equation), intent(inout) :: this

    The routine is called on this equation.

    integer(kind=ip), intent(in) :: dest

    Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

procedure, public :: update_vars => ode_update_vars

The update_vars routine is provided by ode_update_vars.

  • interface

    public module subroutine ode_update_vars(this, source, dest, source2, scalar, scalar2)

    The interface for the ODE version of update_vars. This interface is consistent with eq_update_vars_interface.

    Arguments

    Type IntentOptional AttributesName
    class(ode_equation), intent(inout), target:: this

    The routine is called on this equation.

    integer(kind=ip), intent(in) :: source

    The first source for the update. Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

    integer(kind=ip), intent(in) :: dest

    The destination for the update. Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

    integer(kind=ip), intent(in), optional :: source2

    The second source for the update. Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

    real(kind=wp), intent(in), optional :: scalar

    The scalar multiplying the first source.

    real(kind=wp), intent(in), optional :: scalar2

    The scalar multiplying the second source.

procedure, public :: print_data => ode_print_data

The print_data routine is provided by ode_print_data.

  • interface

    public module subroutine ode_print_data(this)

    The interface for the ODE version of print_data. This interface is consistent with eq_print_data.

    Arguments

    Type IntentOptional AttributesName
    class(ode_equation), intent(inout) :: this

    The routine is called on this equation.

procedure, public :: init => geod_schw_init

The init routine is provided by geod_schw_init.

  • interface

    public module subroutine geod_schw_init(this)

    The interface for the geod_schw version of init. This interface is consistent with eq_init_interface.

    Arguments

    Type IntentOptional AttributesName
    class(geod_schw), intent(inout), target:: this

    The equation that is being initialized.

procedure, public :: rhs => geod_schw_rhs

The rhs routine is provided by geod_schw_rhs.

  • interface

    public module subroutine geod_schw_rhs(this)

    The interface for the geod_schw version of rhs. This interface is consistent with eq_rhs_interface.

    Arguments

    Type IntentOptional AttributesName
    class(geod_schw), intent(inout) :: this

    The equation for which the RHS is calculated.

procedure, public :: output => geod_schw_output

The output routine is provided by geod_schw_output.

  • interface

    public module subroutine geod_schw_output(this)

    The interface for the geod_schw version of output. This interface is consistent with eq_output.

    Arguments

    Type IntentOptional AttributesName
    class(geod_schw), intent(inout) :: this

    The routine is called on this equation.

procedure, public :: save_globals_1 => geod_schw_save_globals_1

The save_globals_1 routine is provided by geod_schw_save_globals_1.

procedure, public :: save_globals_2 => geod_schw_save_globals_2

The save_globals_2 routine is provided by geod_schw_save_globals_2.

procedure, public :: load_globals => geod_schw_load_globals

The load_globals routine is provided by geod_schw_load_globals.

  • interface

    public module subroutine geod_schw_load_globals(this)

    The interface for the geod_schw version of load_globals. This interface is consistent with eq_load_globals.

    Arguments

    Type IntentOptional AttributesName
    class(geod_schw), intent(inout) :: this

    The routine is called on this equation.

Source Code

  type, extends(ode_equation) :: geod_schw
  !! A class that defines the geodesic evolution equations for a particle
  !! moving in a Schwarzschild spacetime.
  !!
  !! For this system [[geod_schw:nvars]]=7. The quantities stored in
  !! [[geod_schw:var_data]] are 1: \(r\), 2: \(\phi\), 3: \(u^t\),
  !! 4: \(u^r\), 5: \(u^{\phi}\), 6: \(m_q\), 7: \(\chi\), where
  !! \(r\) is the radial coordinate in Schwarzschild coordinates, \(\phi\)
  !! is the azimuthal angle,
  !! \(u^t, u^r\) and \(u^{\phi}\) are the time, radial and \(\phi\)
  !! components of the 4-velocity, \(m_q\) is the mass of the scalar charge
  !! and \(\chi\) s a variable defined in the osculating orbits
  !! framework that varies from \(0\) to \(2\pi\) over a full radial cycle.
  !! Note that \(m_q\) is stricly constant for all other cases than a
  !! scalar charge and should stricly not be included in a generic geodesic
  !! evolution. Also \(\chi\) is included for convenience as it is useful to
  !! control the turn on of the back-reaction in terms of timescales related
  !! to the radial cycle.
    real(wp) :: En
    !! The orbital energy per unit mass.
    real(wp) :: Lz
    !! The orbital angular momentum per unit mass.
    real(wp) :: e
    !! The orbital eccentricity.
    real(wp) :: p
    !! The orbital semi-latus rectum.
    real(wp) :: w
    !! The value of \(\chi\) at periapsis.
    real(wp) :: d2rdt2
    !! The second time derivative of the radial coordinate. Needed for the
    !! time dependent coordinate transformation.
    real(wp), dimension(4) :: force
    !! The self-force or any external force \(f_{\mu}\).
    real(wp), dimension(4) :: accel
    !! The acceleration \(a^{\mu}=
    !!   \frac{q}{m_q}(g^{\mu\nu}+u^{\mu}u^{\nu})f_{\nu}\).
    real(wp) :: udota
    !! The dot-product of the 4-velocity and the force \(q\, u^{\mu}f_{\mu}\).
  contains
    procedure :: init => geod_schw_init
    !! The [[equation:init]] routine is provided by [[geod_schw_init]].
    procedure :: rhs => geod_schw_rhs
    !! The [[equation:rhs]] routine is provided by [[geod_schw_rhs]].
    procedure :: output => geod_schw_output
    !! The [[equation:output]] routine is provided by [[geod_schw_output]].
    procedure :: save_globals_1 => geod_schw_save_globals_1
    !! The [[equation:save_globals_1]] routine is provided by
    !! [[geod_schw_save_globals_1]].
    procedure :: save_globals_2 => geod_schw_save_globals_2
    !! The [[equation:save_globals_2]] routine is provided by
    !! [[geod_schw_save_globals_2]].
    procedure :: load_globals => geod_schw_load_globals
    !! The [[equation:load_globals]] routine is provided by
    !! [[geod_schw_load_globals]].
    final :: close_geod_schw
    !! The finalizer.
  end type geod_schw