eff_source Derived Type

type, public, abstract :: eff_source

An abstract effective source interface.


Inherits

type~~eff_source~~InheritsGraph type~eff_source 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~~eff_source~~InheritedByGraph type~eff_source eff_source type~sing_observer sing_observer type~sing_observer->type~eff_source p type~scal_schw_eff scal_schw_eff type~scal_schw_eff->type~eff_source 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).


Type-Bound Procedures

procedure(eff_source_init), public, deferred, pass :: init

The constructor.

  • subroutine eff_source_init(this, nmodes, nvars, l, m, mass) Prototype

    The interface of the constructor.

    Arguments

    Type IntentOptional AttributesName
    class(eff_source), 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(eff_source_set_time_window), public, deferred, pass :: set_time_window

Routine to set a time window.

  • subroutine eff_source_set_time_window(this, tfac, dtfac_dt, d2tfac_dt2, do_smooth_after_lmax) Prototype

    The interface of the routine that sets the time window for smooth turn on of the effective source.

    Arguments

    Type IntentOptional AttributesName
    class(eff_source), 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(eff_source_set_particle_pos), public, deferred, pass :: set_particle_pos

Routine to specify the current state of the particle.

  • subroutine eff_source_set_particle_pos(this, r, phi, ur, En, Lz, ar, aphi, dardt, daphidt, d2ardt2, d2aphidt2) Prototype

    The interface of the routine that sets the state of the particle.

    Arguments

    Type IntentOptional AttributesName
    class(eff_source), 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(eff_source_evaluate_source), public, deferred, pass :: evaluate_source

Routine to evaluate the effective source.

  • subroutine eff_source_evaluate_source(this, r, wt) Prototype

    The interface of the routine that evaluates the effective source.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(eff_source), 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(eff_source_get_singular), public, deferred, pass :: get_singular

Routine to get the singular field at a given radius.

  • subroutine eff_source_get_singular(this, r, mode, psi) Prototype

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

    Arguments

    Type IntentOptional AttributesName
    class(eff_source), 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(eff_source_get_dsingular_dt), public, deferred, pass :: get_dsingular_dt

Routine to get the time derivative of the singular field at a given radius.

  • subroutine eff_source_get_dsingular_dt(this, r, mode, dpsidt) Prototype

    The 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(eff_source), 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(eff_source_get_dsingular_dr), public, deferred, pass :: get_dsingular_dr

Routine to get the radial derivative of the singular field at a given radius.

  • subroutine eff_source_get_dsingular_dr(this, r, mode, dpsidr) Prototype

    The 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(eff_source), 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, abstract :: eff_source
  !! An abstract effective source interface.
    integer(ip) :: nmodes
    !! The number of modes an effective source is provided for.
    integer(ip) :: nvars
    !! The number of variables an effective source is provided for.
    type(cgf), dimension(:,:), allocatable :: source
    !! A 2d-array of complex grid functions. When allocated the size is
    !! ([[eff_source:nvars]]:[[eff_source:nmodes]]).
  contains
    procedure (eff_source_init), deferred, pass :: init
    !! The constructor.
!    procedure (eff_source_set_window), deferred, pass :: set_window
!    procedure (eff_source_calc_window), deferred, pass :: calc_window    
    procedure (eff_source_set_time_window), deferred, pass :: set_time_window
    !! Routine to set a time window.
    procedure (eff_source_set_particle_pos), deferred, pass :: set_particle_pos
    !! Routine to specify the current state of the particle.
    procedure (eff_source_evaluate_source), deferred, pass :: evaluate_source
    !! Routine to evaluate the effective source.
    procedure (eff_source_get_singular), deferred, pass :: get_singular
    !! Routine to get the singular field at a given radius.
    procedure (eff_source_get_dsingular_dt), deferred, pass :: get_dsingular_dt
    !! Routine to get the time derivative of the singular field at a given
    !! radius.
    procedure (eff_source_get_dsingular_dr), deferred, pass :: get_dsingular_dr
    !! Routine to get the radial derivative of the singular field at a given
    !! radius.
  end type eff_source