sf_observer Derived Type

type, public, extends(observer) :: sf_observer

A class that defines an observer of the self-force for a scalar charge in orbit around a Schwarzschild black hole.


Inherits

type~~sf_observer~~InheritsGraph type~sf_observer sf_observer type~observer observer type~sf_observer->type~observer type~scal_schw scal_schw type~sf_observer->type~scal_schw p type~cgf cgf type~scal_schw->type~cgf eq_flux_data type~rgf rgf type~scal_schw->type~rgf eq_coeffs, eq_lcoeffs, r_schw, r_star type~ref_element ref_element type~scal_schw->type~ref_element refelem type~rgfb rgfb type~scal_schw->type~rgfb eq_lambda, eq_s, eq_sinv type~scal_schw_eff scal_schw_eff type~scal_schw->type~scal_schw_eff effs type~cpde_equation cpde_equation type~scal_schw->type~cpde_equation type~tdc tdc type~scal_schw->type~tdc time_dep_coord type~element_cdata element_cdata type~cgf->type~element_cdata elems type~gf gf type~cgf->type~gf type~rgf->type~gf type~element_rdata element_rdata type~rgf->type~element_rdata elems type~element_boundary_rdata element_boundary_rdata type~rgfb->type~element_boundary_rdata elems type~gfb gfb type~rgfb->type~gfb type~eff_source eff_source type~scal_schw_eff->type~eff_source type~cpde_equation->type~cgf eq_data, eq_rhs_data, eq_tmp_data type~cgf_pointer cgf_pointer type~cpde_equation->type~cgf_pointer data_pointer type~equation equation type~cpde_equation->type~equation type~tdc->type~rgf dxdlambda, dxdxi, d2xdlambda2, d2xdxi2, d2xdlambdadxi, rm2m type~tdc->type~rgfb dxdlambda_b, dxdxi_b type~element_data element_data type~element_cdata->type~element_data type~cgf_pointer->type~cgf p type~gf_pointer gf_pointer type~cgf_pointer->type~gf_pointer type~element_boundary_data element_boundary_data type~element_boundary_rdata->type~element_boundary_data type~eff_source->type~cgf source type~element_rdata->type~element_data

Contents

Source Code


Components

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

The number of radii the observer should observe at.

integer(kind=ip), public :: ioo_id

The file unit number this observer should use for output.

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

The name of the observer.

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

A 1d-array containing the radii that the observer should observe at. On allocation the size is nradii.

integer(kind=ip), public, dimension(:), allocatable:: elem_index

A 1d-array containing the index of all the elements that contains radii.

integer(kind=ip), public, dimension(:), allocatable:: node_index

A 1d-array containing the node index within all the elements that contains radii.

type(scal_schw), public, pointer:: p

A pointer to the scal_schw equation that provides the data.

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

The -modes of the regular field at the particle location.

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

The -modes of the time derivative of the regular field at the particle location.

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

The -modes of the derivative of the regular field at the particle location.

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

The -modes of the radial derivative of the regular field at the particle location.


Finalization Procedures

final :: close_sf_observer

The finalizer.


Type-Bound Procedures

procedure, public :: init => sf_init

The init routine is provided by sf_init

  • interface

    public module subroutine sf_init(this, rad, coord, object)

    The interface for the sf_observer version of init. This interface is consistent with obs_init_interface.

    Arguments

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

    The self-force observer that is being initialized.

    real(kind=wp), intent(in), dimension(:):: rad

    A 1d-array containing the radii where the observations have to be performed. Obviously it only makes sense to pass in the particle location.

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

    A real grid function containing the coordinates of the grid.

    class(*), intent(in), target:: object

    The object on which observations have to be done. This has to be of type scal_schw.

procedure, public :: extract => sf_extract

The extract routine is provided by sf_extract

procedure, public :: output => sf_output

The output routine is provided by sf_output

Source Code

  type, extends(observer) :: sf_observer
  !! A class that defines an observer of the self-force for a scalar charge
  !! in orbit around a Schwarzschild black hole.
    type(scal_schw), pointer :: p
    !! A pointer to the [[scal_schw]] equation that provides the data.
    real(wp), dimension(:), allocatable :: fl
    !! The \(\ell\)-modes of the regular field at the particle location.
    real(wp), dimension(:), allocatable :: ftl
    !! The \(\ell\)-modes of the time derivative of the regular field at the
    !! particle location.
    real(wp), dimension(:), allocatable :: fphil
    !! The \(\ell\)-modes of the \(\phi\) derivative of the regular field at
    !! the particle location.
    real(wp), dimension(:), allocatable :: frl
    !! The \(\ell\)-modes of the radial derivative of the regular field at the
    !! particle location.
  contains
    procedure :: init => sf_init
    !! The [[observer:init]] routine is provided by [[sf_init]]
    procedure :: extract => sf_extract
    !! The [[observer:extract]] routine is provided by [[sf_extract]]
    procedure :: output => sf_output 
    !! The [[observer:output]] routine is provided by [[sf_output]]
    final :: close_sf_observer
    !! The finalizer.
  end type sf_observer