scalar_schw Module

Module that defines an equation class for evolving the spherical harmonic decomposed field of a scalar point charge moving in a Schwarzschild spacetime. From the starting point of the wave equation in Tortoise coordinates, the class supports the use of hyperboloidal coordinates in regions near the horizon and near future null infinity as well as time dependent coordinates for the case of a particle on a non-circular orbit. The class interfaces with an effective source provided as C++ routines.

The wave equation is written in first order in time and space form with the evolved variables being where is the radial coordinate and is the time.

The implementation is found in submodule_scalar_schw_implementation.f90.


Uses

  • module~~scalar_schw~~UsesGraph module~scalar_schw scalar_schw module~scalar_schw_eff scalar_schw_eff module~scalar_schw->module~scalar_schw_eff module~orbit_base orbit_base module~scalar_schw->module~orbit_base module~kinds kinds module~scalar_schw->module~kinds module~time_dependent_coordinate time_dependent_coordinate module~scalar_schw->module~time_dependent_coordinate module~grid_function grid_function module~scalar_schw->module~grid_function module~dg_structures DG_structures module~scalar_schw->module~dg_structures module~pde_equations pde_equations module~scalar_schw->module~pde_equations iso_c_binding iso_c_binding module~scalar_schw->iso_c_binding module~scalar_schw_eff->module~kinds module~scalar_schw_eff->iso_c_binding module~effective_source effective_source module~scalar_schw_eff->module~effective_source module~orbit_base->module~kinds module~time_dependent_coordinate->module~kinds module~time_dependent_coordinate->module~grid_function module~grid_function->module~kinds module~element element module~grid_function->module~element module~dg_structures->module~kinds module~pde_equations->module~kinds module~pde_equations->module~grid_function module~equations equations module~pde_equations->module~equations module~element->module~kinds module~equations->module~kinds module~effective_source->module~kinds module~effective_source->module~grid_function module~effective_source->iso_c_binding module~world_tube world_tube module~effective_source->module~world_tube module~world_tube->module~kinds module~world_tube->module~grid_function

Used by

  • module~~scalar_schw~~UsedByGraph module~scalar_schw scalar_schw proc~scal_schw_eff_init scal_schw_eff_init proc~scal_schw_eff_init->module~scalar_schw module~scalar_schw_implementation scalar_schw_implementation module~scalar_schw_implementation->module~scalar_schw program~test test program~test->module~scalar_schw module~self_force_observer self_force_observer program~test->module~self_force_observer module~self_force_observer->module~scalar_schw proc~scal_schw_save_globals_2 scal_schw_save_globals_2 proc~scal_schw_save_globals_2->module~self_force_observer module~self_force_observer_implementation self_force_observer_implementation module~self_force_observer_implementation->module~self_force_observer

Contents


Variables

TypeVisibility AttributesNameInitial
complex(kind=wp), public, dimension(:,:), allocatable:: drho

A 2d array of reals used to store the radial derivative of for all modes in a single element. The size when allocated is (order+1:nmodes).

complex(kind=wp), public, dimension(:,:), allocatable:: dpi

A 2d array of reals used to store the radial derivative of for all modes in a single element. The size when allocated is (order+1:nmodes).

complex(kind=wp), public, dimension(:,:,:), allocatable:: flux_result

A 3d array of complex used to store fluxes for all modes at the boundary of a single element. The size when allocated is (order+1:2:nmodes).


Interfaces

interface

  • public module function convert_var_name(var_name, mode)

    A helper function that produces unique file names by adding the mode number to a variable name.

    Arguments

    Type IntentOptional AttributesName
    character(len=*), intent(in) :: var_name

    The input variable name.

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

    the mode number.

    Return Value character(len=len(var_name)+5)

    The return value is the converted variable name.

interface

  • public module subroutine scal_schw_init(this)

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

    Arguments

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

    The equation that is being initialized.

interface

  • public module subroutine scal_schw_rhs(this)

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

    Arguments

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

    The equation for which the RHS is calculated.

interface

interface

interface

interface

  • public module subroutine scal_schw_flux(this)

    The interface for the scal_schw_flux routine for calculating fluxes. Can be called under the generic name flux.

    Arguments

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

    The routine is called on this equation.

interface

  • public module subroutine read_all_modes(this)

    The interface for the read_all_modes routine that reads external initial data.

    Arguments

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

    The routine is called on this equation.

interface

  • public module subroutine output_coords(this)

    The interface for the output_coords routine that writes out the coordinates for an external python frequency domain code that calculates initial data.

    Arguments

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

    The routine is called on this equation.

interface

  • public module subroutine tortoise_to_hyperboloidal(this, elem, node, inner, dpsidt, dpsidr)

    The interface for the tortoise_to_hyperboloidal routine that converts from Tortoise to hyperboloidal coordinates when reading in external initial data.

    Arguments

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

    The routine is called on this equation.

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

    The index of the element where the transformation is calculated.

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

    The index of the node within that element where the transformation is calculated.

    logical, intent(in) :: inner

    If .true. use the transformation for the inner region. If .false. use the transformation for the outer region.

    complex(kind=wp), intent(inout) :: dpsidt

    On input holds the time derivative in Tortoise coordinates. On output holds the time derivative in hyperboloidal coordinates.

    complex(kind=wp), intent(inout) :: dpsidr

    On input holds the radial derivative in Tortoise coordinates. On output holds the radial derivative in hyperboloidal coordinates.


Derived Types

type, public, extends(cpde_equation) :: scal_schw

A class that defines the evolution equations for a scalar field produced by a point charge in Schwarzschild coordinates decomposed into spherical harmonics.

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 :: nmodes

The number of spherical harmonic modes. Should be moved to the specific implementation of the equation as this class should not be limited to systems using spherical harmonic decomposition.

integer(kind=ip), public :: nvars =3

The number of variables per mode. Should probably be changed to be the total number of variables in order to make this independent of spherical harmonic decomposition. And the value should be set by the equation implementation.

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

A 2d array of complex grid functions that contains the data variables for the equation system. Should probably be changed to a 1d array to make this independent of spherical harmonic decomposition.

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

A 2d array of complex grid functions that contains the rhs variables for the equation system. Should probably be changed to a 1d array to make this independent of spherical harmonic decomposition.

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

A 3d array of complex grid functions that contains the temporary variables needed by the time integrator. Should probably be changed to a 2d array to make this independent of spherical harmonic decomposition.

type(cgf_pointer), public, dimension(:,:,:), allocatable:: data_pointer

A 3d array of pointers to complex grid functions that points to the RHS variables (:,:,-1), the data variables (:,:,0) and the temporary variables (:,:,1:ntmp) for the equation system. Should probably be changed to a 2d array to make this independent of spherical harmonic decomposition.

integer(kind=c_int), public, dimension(:), allocatable:: ll

A 1d array of c_int containing the l values of all the evolved modes.

integer(kind=c_int), public, dimension(:), allocatable:: mm

A 1d array of c_int containing the m values of all the evolved modes.

type(ref_element), public :: refelem

The ref_element contains the derivative matrix needed for approximating partial derivatives as well as the routines needed for calculating characteristic fluxes.

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

A 2d array of complex grid functions that stores flux data for the system.

type(rgf), public, dimension(:), allocatable:: eq_coeffs

A 1d array of real grid functions that stores the equation coefficients.

type(rgf), public, dimension(:), allocatable:: eq_lcoeffs

A 1d array of real grid functions that stores the l-dependent potential.

type(rgfb), public, dimension(:), allocatable:: eq_lambda

A 1d array of real boundary grid functions that stores the characteristic speeds at the element boundaries.

type(rgfb), public, dimension(:,:), allocatable:: eq_s

A 2d array of real boundary grid functions that stores the matrix used to convert from characteristic to evolved variables.

type(rgfb), public, dimension(:,:), allocatable:: eq_sinv

A 2d array of real boundary grid functions that stores the matrix used to convert from evolve to characteristic variables.

type(rgf), public :: r_schw

A real grid function that stores the Schwarzschild radial coordinate.

type(rgf), public :: r_star

A real grid function that stores the tortoise radial coordinate.

type(scal_schw_eff), public :: effs

The effective source for a scalar point charge on generic orbits in a Schwarzschild spacetime.

type(tdc), public :: time_dep_coord

A time dependent coordinate class for the scalar wave equation in Tortoise coordinates.

Type-Bound Procedures

procedure, public :: set_to_zero => cpde_set_to_zero

The set_to_zero routine is provided by cpde_set_to_zero.

procedure, public :: update_vars => cpde_update_vars

The update_vars routine is provided by cpde_update_vars.

procedure, public :: output => cpde_output

The output routine is provided by cpde_output.

procedure, public :: print_data => cpde_print_data

The print_data routine is provided by cpde_print_data.

procedure, public :: init => scal_schw_init

The init routine is provided by scal_schw_init.

procedure, public :: rhs => scal_schw_rhs

The rhs routine is provided by scal_schw_rhs.

procedure, public :: save_globals_1 => scal_schw_save_globals_1

The save_globals_1 routine is provided by scal_schw_save_globals_1.

procedure, public :: save_globals_2 => scal_schw_save_globals_2

The save_globals_2 routine is provided by scal_schw_save_globals_2.

procedure, public :: load_globals => scal_schw_load_globals

The load_globals routine is provided by scal_schw_load_globals.

generic, public :: flux => scal_schw_flux

A routine to calculate fluxes is provided by scal_schw_flux under the generic name flux.

procedure, public :: scal_schw_flux

Provides a routine to calculate fluxes.

procedure, public :: read_all_modes

Provides a routine to read in external initial data.

procedure, public :: output_coords

Provides a routine to output the coordinates in a format needed for a frequency domain python code that can provide initial data.

procedure, public :: tortoise_to_hyperboloidal

Provides a routine to transform from tortoise to hyperboloid that is used when reading in external data.