time_dependent_coordinate Module

Module that defines the interface for a class that provides the routines necessary for the use of time dependent coordinates. This is currently tied to supporting the scalar wave equation on a Schwarzschild background provided in scalar_schw.

Starting from Tortoise coordinates the equations are transformed to time dependent coordinate as descibed in Field, Hesthaven & Lau, Class. Quant. Grav. 26 (2009) 165010.

The implementation is provided in submodule_time_dependent_coordinate_implementation.f90.


Uses

  • module~~time_dependent_coordinate~~UsesGraph module~time_dependent_coordinate time_dependent_coordinate module~grid_function grid_function module~time_dependent_coordinate->module~grid_function module~kinds kinds module~time_dependent_coordinate->module~kinds module~grid_function->module~kinds module~element element module~grid_function->module~element module~element->module~kinds

Used by

  • module~~time_dependent_coordinate~~UsedByGraph module~time_dependent_coordinate time_dependent_coordinate module~scalar_schw scalar_schw module~scalar_schw->module~time_dependent_coordinate module~time_dependent_coordinate_implementation time_dependent_coordinate_implementation module~time_dependent_coordinate_implementation->module~time_dependent_coordinate 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


Interfaces

interface

  • public module subroutine tdc_init(this)

    The interface for the initialization routine.

    Arguments

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

    This time dependent coordinate object is being initialized.

interface

  • public module subroutine tdc_set_coefficients(this, coeffs, lcoeffs, lambda, s, sinv, rho, rstar, rschw, ll)

    The interface for the routine that sets the coefficient for the scalar wave equation in Schwarzschild spacetime.

    Arguments

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

    The routine is called on this time dependent coordinate object.

    type(rgf), intent(inout), dimension(:):: coeffs

    A 1d array of real grid functions containing the wave equation coefficients (should be eq_coeffs). On output it will contain .

    type(rgf), intent(inout), dimension(:):: lcoeffs

    A 1d array of real grid functions containing the dependent coefficients (should be eq_lcoeffs). On output it will contain the potential for all modes.

    type(rgfb), intent(inout), dimension(:):: lambda

    A 1d array of real boundary grid functions containing the characteristic speeds at the boundary of the elements (should be eq_lambda). On output it will be updated.

    type(rgfb), intent(inout), dimension(:,:):: s

    A 2d array of real boundary grid functions containing the matrix used to convert from characteristic to evolved variables (should be eq_s). On output it will be updated.

    type(rgfb), intent(inout), dimension(:,:):: sinv

    A 2d array of real boundary grid functions containing the matrix used to convert from evolved to characteristic variables (should be eq_sinv). On output it will be updated.

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

    A real grid function containing the computational radial coordinate, .

    type(rgf), intent(inout) :: rstar

    A real grid function containing the tortoise radial coordinate, . On output this will be updated.

    type(rgf), intent(inout) :: rschw

    A real grid function containing the Schwarzschild radial coodrinate, . On output this will be updated.

    integer(kind=c_int), intent(in), dimension(:):: ll

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

interface

  • public module subroutine tdc_tdc_to_tortoise_cvec(this, ielem, dir, dudlambda, dudxi, dudt, dudrstar)

    Routine to transform from time dependent to tortoise coordinates for complex vector input at element boundaries.

    Arguments

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

    The routine is called on this time dependent coordinate object.

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

    The index of the element that contains the coordinate transformation information.

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

    The index of the boundary within the element that contains the coordinate transformation. Left boundary: 1, right boundary: 2.

    complex(kind=wp), intent(in), dimension(:):: dudlambda

    The vector of values to transform.

    complex(kind=wp), intent(in), dimension(:):: dudxi

    The vector of values to transform.

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

    On output contains the vector.

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

    On output contains the vector.

interface

  • public module subroutine tdc_tdc_to_tortoise_cscal(this, ielem, dir, dudlambda, dudxi, dudt, dudrstar)

    Routine to transform from time dependent to tortoise coordinates for complex scalar input at element boundaries.

    Arguments

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

    The routine is called on this time dependent coordinate object.

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

    The index of the element that contains the coordinate transformation information.

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

    The index of the boundary within the element that contains the coordinate transformation. Left boundary: 1, right boundary: 2.

    complex(kind=wp), intent(in) :: dudlambda

    The value of to transform.

    complex(kind=wp), intent(in) :: dudxi

    The value of to transform.

    complex(kind=wp), intent(out) :: dudt

    On output contains the value.

    complex(kind=wp), intent(out) :: dudrstar

    On output contains the value.

interface

  • public module subroutine tdc_tdc_to_tortoise_rscal(this, ielem, dir, dudlambda, dudxi, dudt, dudrstar)

    Routine to transform from time dependent to tortoise coordinates for real scalar input at element boundaries.

    Arguments

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

    The routine is called on this time dependent coordinate object.

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

    The index of the element that contains the coordinate transformation information.

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

    The index of the boundary within the element that contains the coordinate transformation. Left boundary: 1, right boundary: 2.

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

    The value of to transform.

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

    The value of to transform.

    real(kind=wp), intent(out) :: dudt

    On output contains the value.

    real(kind=wp), intent(out) :: dudrstar

    On output contains the value.

interface

  • public module subroutine tdc_tortoise_to_tdc_cvecb(this, ielem, dir, dudt, dudrstar, dudlambda, dudxi)

    Routine to transform from tortoise coordinates to time dependent for complex vector input at element boundaries.

    Arguments

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

    The routine is called on this time dependent coordinate object.

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

    The index of the element that contains the coordinate transformation information.

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

    The index of the boundary within the element that contains the coordinate transformation. Left boundary: 1, right boundary: 2.

    complex(kind=wp), intent(in), dimension(:):: dudt

    The vector of to transform.

    complex(kind=wp), intent(in), dimension(:):: dudrstar

    The vector of to transform.

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

    On output contains the vector.

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

    On output contains the vector.

interface

  • public module subroutine tdc_tortoise_to_tdc_cscalb(this, ielem, dir, dudt, dudrstar, dudlambda, dudxi)

    Routine to transform from tortoise coordinates to time dependent for complex scalar input at element boundaries.

    Arguments

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

    The routine is called on this time dependent coordinate object.

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

    The index of the element that contains the coordinate transformation information.

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

    The index of the boundary within the element that contains the coordinate transformation. Left boundary: 1, right boundary: 2.

    complex(kind=wp), intent(in) :: dudt

    The value of to transform.

    complex(kind=wp), intent(in) :: dudrstar

    The value of to transform.

    complex(kind=wp), intent(out) :: dudlambda

    On output contains the value.

    complex(kind=wp), intent(out) :: dudxi

    On output contains the value.

interface

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

    Routine to transform from tortoise coordinates to time dependent for complex scalar input.

    Arguments

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

    The routine is called on this time dependent coordinate object.

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

    The element index of the point to transform.

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

    The node index of the point to transform.

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

    On input contains: . On output contains .

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

    On input contains: . On output contains .


Derived Types

type, public :: tdc

A class that defines a time dependent coordinate transformation for the scalar wave equation on s Schwarzschild spacetime.

Components

TypeVisibility AttributesNameInitial
type(rgfb), public :: dxdlambda_b

A real boundary grid function that stores on the element boundaries.

type(rgfb), public :: dxdxi_b

A real boundary grid function that stores on the element boundaries.

real(kind=wp), public :: maxspeed

The maximum coordinate speed (needed for CFL timestep condition).

type(rgf), public :: dxdlambda

A real grid function that stores everywhere.

type(rgf), public :: dxdxi

A real grid function that stores everywhere.

type(rgf), public :: d2xdlambda2

A real grid function that stores everywhere.

type(rgf), public :: d2xdxi2

A real grid function that stores everywhere.

type(rgf), public :: d2xdlambdadxi

A real grid function that stores everywhere.

type(rgf), public :: rm2m

A real grid function that stores everywhere.

Type-Bound Procedures

procedure, public :: init => tdc_init

The initialization routine.

procedure, public :: set_coefficients => tdc_set_coefficients

The routine that sets the coefficients for the wave equation.

procedure, public :: tdc_to_tortoise_cvec => tdc_tdc_to_tortoise_cvec

Routine to transform from to for complex vector arguments at the boundary of an element.

procedure, public :: tdc_to_tortoise_cscal => tdc_tdc_to_tortoise_cscal

Routine to transform from to for complex scalar arguments at the boundary of an element.

procedure, public :: tdc_to_tortoise_rscal => tdc_tdc_to_tortoise_rscal

Routine to transform from to for real scalar arguments at the boundary of an element.

generic, public :: tdc_to_tortoise => tdc_to_tortoise_cvec, tdc_to_tortoise_cscal, tdc_to_tortoise_rscal

Generic name for routines that transform from to at the boundary of an element.

procedure, public :: tortoise_to_tdc_cvecb => tdc_tortoise_to_tdc_cvecb

Routine to transform from to for complex vector arguments at the boundary of an element.

procedure, public :: tortoise_to_tdc_cscalb => tdc_tortoise_to_tdc_cscalb

Routine to transform from to for complex scalar arguments at the boundary of an element.

procedure, public :: tortoise_to_tdc_cscal => tdc_tortoise_to_tdc_cscal

Routine to transform from to for complex scalar arguments at any node in any element.

generic, public :: tortoise_to_tdc => tortoise_to_tdc_cvecb, tortoise_to_tdc_cscalb, tortoise_to_tdc_cscal

Generic name for routines that transform from to .