scal_schw_eff Derived Type

type, public, extends(eff_source) :: scal_schw_eff

A class that interfaces with a C++ class that provides an effective source for a scalar charge on a generic accelerated orbit around a Schwarzschild black hole.


Inherits

type~~scal_schw_eff~~InheritsGraph type~scal_schw_eff scal_schw_eff type~eff_source eff_source type~scal_schw_eff->type~eff_source type~cgf cgf type~eff_source->type~cgf source type~gf gf type~cgf->type~gf type~element_cdata element_cdata type~cgf->type~element_cdata elems type~element_data element_data type~element_cdata->type~element_data

Inherited by

type~~scal_schw_eff~~InheritedByGraph type~scal_schw_eff scal_schw_eff type~scal_schw scal_schw type~scal_schw->type~scal_schw_eff effs type~sf_observer sf_observer type~sf_observer->type~scal_schw p

Contents

Source Code


Components

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

The number of modes an effective source is provided for.

integer(kind=ip), public :: nvars

The number of variables an effective source is provided for.

type(cgf), public, dimension(:,:), allocatable:: source

A 2d-array of complex grid functions. When allocated the size is (nvars:nmodes).

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

A 2d-array of reals to hold the real part of the effective source for all nodes in a DG element and for all modes. When allocated the size is (order+1:nmodes).

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

A 2d-array of reals to hold the complex part of the effective source for all nodes in a DG element and for all modes. When allocated the size is (order+1:nmodes).


Type-Bound Procedures

procedure, public :: init => scal_schw_eff_init

The init routine is provided by scal_schw_eff_init.

  • interface

    public module subroutine scal_schw_eff_init(this, nmodes, nvars, l, m, mass)

    Interface of the constructor compatible with init.

    Arguments

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

    On return, the constructed object.

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

    The number of modes.

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

    The number of variables.

    integer(kind=c_int), intent(in), dimension(nmodes):: l

    A 1d array of size nmodes containing the -values of the modes.

    integer(kind=c_int), intent(in), dimension(nmodes):: m

    A 1d array of size nmodes containing the m-values of the modes.

    real(kind=wp), intent(in) :: mass

    The mass of the black hole.

procedure, public :: set_time_window => scal_schw_eff_set_time_window

The set_particle_pos routine is provided by scal_schw_eff_set_particle_pos.

  • interface

    public module subroutine scal_schw_eff_set_time_window(this, tfac, dtfac_dt, d2tfac_dt2, do_smooth_after_lmax)

    Interface to the set_time_window routine compatible with set_time_window.

    Arguments

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

    The routine is called on this object.

    real(kind=wp), intent(in) :: tfac

    The current value for the time window.

    real(kind=wp), intent(in) :: dtfac_dt

    The current value for the time derivative of the time window.

    real(kind=wp), intent(in) :: d2tfac_dt2

    The current value for the second time derivative of the time window.

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

    If do_smooth_after_lmax use tfac=1, dtfac_dt=0, d2tfac_dt2=0. This allows for smooth turn on of the effective source for the modes with do_smooth_after_lmax, while the rest gets turned on instantaneously (e.g. when external initial data is available).

procedure, public :: set_particle_pos => scal_schw_eff_set_particle_pos

The set_particle_pos routine is provided by scal_schw_eff_set_particle_pos.

  • interface

    public module subroutine scal_schw_eff_set_particle_pos(this, r, phi, ur, En, Lz, ar, aphi, dardt, daphidt, d2ardt2, d2aphidt2)

    Interface of the routine that sets the state of the particle.

    Arguments

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

    The routine is called on this object.

    real(kind=wp), intent(in) :: r

    The radial coordinate of the particle (in Schwarzschild coordinates), .

    real(kind=wp), intent(in) :: phi

    The azimuthal angle of the particle, .

    real(kind=wp), intent(in) :: ur

    The radial component of the 4-velocity, .

    real(kind=wp), intent(in) :: En

    The energy per unit mass of the particle, .

    real(kind=wp), intent(in) :: Lz

    The angular momentum per unit mass of the particle .

    real(kind=wp), intent(in) :: ar

    The radial component of the 4-acceleration, .

    real(kind=wp), intent(in) :: aphi

    The -component of the 4-acceleration, .

    real(kind=wp), intent(in) :: dardt

    The derivative of with respect to Schwarzschild coordinate time.

    real(kind=wp), intent(in) :: daphidt

    The derivative of with respect to Schwarzschild coordinate time.

    real(kind=wp), intent(in) :: d2ardt2

    The second derivative of with respect to Schwarzschild coordinate time.

    real(kind=wp), intent(in) :: d2aphidt2

    The second derivative of with respect to Schwarzschild coordinate time.

procedure, public :: evaluate_source => scal_schw_eff_evaluate_source

The evaluate_source routine is provided by scal_schw_eff_evaluate_source.

  • interface

    public module subroutine scal_schw_eff_evaluate_source(this, r, wt)

    Interface of the routine that evaluates the effective source.

    Read more…

    Arguments

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

    The routine is called on this object.

    type(rgf), intent(in) :: r

    A real values grid function that contain the radial coordinate (in Schwarzschild coordinates).

    type(wtube), intent(in) :: wt

    A world-tube object that ensures that the effective source is only non-zero inside the world-tube.

procedure, public :: get_singular => scal_schw_eff_get_singular

The get_singular routine is provided by scal_schw_eff_get_singular.

  • interface

    public module subroutine scal_schw_eff_get_singular(this, r, mode, psi)

    Interface of the routine that evaluates the singular field for a given mode and at a given radial coordinate.

    Arguments

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

    The routine is called on this object.

    real(kind=wp), intent(in) :: r

    The radial coordinate (Schwarzschild coordinates).

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

    The mode.

    complex(kind=wp), intent(out), dimension(:):: psi

    A 1d-array of size nvars of complex values that on return contains the singular field for all variables.

procedure, public :: get_dsingular_dt => scal_schw_eff_get_dsingular_dt

The get_dsingular_dt routine is provided by scal_schw_eff_get_dsingular_dt.

  • interface

    public module subroutine scal_schw_eff_get_dsingular_dt(this, r, mode, dpsidt)

    Interface of the routine that evaluates the time derivative of the singular field for a given mode and at a given radial coordinate.

    Arguments

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

    The routine is called on this object.

    real(kind=wp), intent(in) :: r

    The radial coordinate (Schwarzschild coordinates).

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

    The mode.

    complex(kind=wp), intent(out), dimension(:):: dpsidt

    A 1d-array of size nvars of complex values that on return contains the time derivative of the singular field for all variables.

procedure, public :: get_dsingular_dr => scal_schw_eff_get_dsingular_dr

The get_dsingular_dr routine is provided by scal_schw_eff_get_dsingular_dr.

  • interface

    public module subroutine scal_schw_eff_get_dsingular_dr(this, r, mode, dpsidr)

    Interface of the routine that evaluates the radial derivative of the singular field for a given mode and at a given radial coordinate.

    Arguments

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

    The routine is called on this object.

    real(kind=wp), intent(in) :: r

    The radial coordinate (Schwarzschild coordinates).

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

    The mode.

    complex(kind=wp), intent(out), dimension(:):: dpsidr

    A 1d-array of size nvars of complex values that on return contains the radial derivative of the singular field for all variables.

Source Code

  type, extends(eff_source) :: scal_schw_eff
  !! A class that interfaces with a C++ class that provides an effective
  !! source for a scalar charge on a generic accelerated orbit around a
  !! Schwarzschild black hole.
    real(wp), dimension(:,:), allocatable :: sre
    !! A 2d-array of reals to hold the real part of the effective source
    !! for all nodes in a DG element and for all modes. When allocated
    !! the size is ([[element_data:order]]+1:[[eff_source:nmodes]]).
    real(wp), dimension(:,:), allocatable :: sim
    !! A 2d-array of reals to hold the complex part of the effective source
    !! for all nodes in a DG element and for all modes. When allocated
    !! the size is ([[element_data:order]]+1:[[eff_source:nmodes]]).
  contains
    procedure :: init => scal_schw_eff_init
    !! The [[eff_source:init]] routine is provided by [[scal_schw_eff_init]].
    procedure :: set_time_window => scal_schw_eff_set_time_window
    !! The [[eff_source:set_particle_pos]] routine is provided by
    !! [[scal_schw_eff_set_particle_pos]].
    procedure :: set_particle_pos => scal_schw_eff_set_particle_pos
    !! The [[eff_source:set_particle_pos]] routine is provided by
    !! [[scal_schw_eff_set_particle_pos]].
    procedure :: evaluate_source => scal_schw_eff_evaluate_source
    !! The [[eff_source:evaluate_source]] routine is provided by
    !! [[scal_schw_eff_evaluate_source]].
    procedure :: get_singular => scal_schw_eff_get_singular
    !! The [[eff_source:get_singular]] routine is provided by
    !! [[scal_schw_eff_get_singular]].
    procedure :: get_dsingular_dt => scal_schw_eff_get_dsingular_dt
    !! The [[eff_source:get_dsingular_dt]] routine is provided by
    !! [[scal_schw_eff_get_dsingular_dt]].
    procedure :: get_dsingular_dr => scal_schw_eff_get_dsingular_dr
    !! The [[eff_source:get_dsingular_dr]] routine is provided by
    !! [[scal_schw_eff_get_dsingular_dr]].
  end type scal_schw_eff