tdc Derived Type

type, public :: tdc

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


Inherits

type~~tdc~~InheritsGraph type~tdc tdc type~rgfb rgfb type~tdc->type~rgfb dxdlambda_b, dxdxi_b type~rgf rgf type~tdc->type~rgf dxdlambda, dxdxi, d2xdlambda2, d2xdxi2, d2xdlambdadxi, rm2m type~gfb gfb type~rgfb->type~gfb type~element_boundary_rdata element_boundary_rdata type~rgfb->type~element_boundary_rdata elems type~gf gf type~rgf->type~gf type~element_rdata element_rdata type~rgf->type~element_rdata elems type~element_boundary_data element_boundary_data type~element_boundary_rdata->type~element_boundary_data type~element_data element_data type~element_rdata->type~element_data

Inherited by

type~~tdc~~InheritedByGraph type~tdc tdc type~scal_schw scal_schw type~scal_schw->type~tdc time_dep_coord type~sf_observer sf_observer type~sf_observer->type~scal_schw p

Contents

Source Code

tdc

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.

  • 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.

procedure, public :: set_coefficients => tdc_set_coefficients

The routine that sets the coefficients for the wave equation.

  • 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.

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.

  • 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.

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.

  • 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.

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.

  • 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.

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.

  • 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.

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.

  • 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.

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.

  • 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 .

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 .

Source Code

  type :: tdc
  !! A class that defines a time dependent coordinate transformation for the
  !! scalar wave equation on s Schwarzschild spacetime.
    type(rgfb) :: dxdlambda_b
    !! A real boundary grid function that stores
    !! \(\frac{\partial r_*}{\partial \lambda}\) on the element boundaries.
    type(rgfb) :: dxdxi_b
    !! A real boundary grid function that stores
    !! \(\frac{\partial r_*}{\partial \xi}\) on the element boundaries.
    real(wp) :: maxspeed
    !! The maximum coordinate speed (needed for CFL timestep condition).
    type(rgf) :: dxdlambda
    !! A real grid function that stores
    !! \(\frac{\partial r_*}{\partial \lambda}\) everywhere.
    type(rgf) :: dxdxi
    !! A real grid function that stores
    !! \(\frac{\partial r_*}{\partial \xi}\) everywhere.
    type(rgf) :: d2xdlambda2
    !! A real grid function that stores
    !! \(\frac{\partial^2 r_*}{\partial \lambda^2}\) everywhere.
    type(rgf) :: d2xdxi2
    !! A real grid function that stores
    !! \(\frac{\partial^2 r_*}{\partial \xi^2}\) everywhere.
    type(rgf) :: d2xdlambdadxi
    !! A real grid function that stores
    !! \(\frac{\partial^2 r_*}{\partial \lambda \partial \xi}\) everywhere.
    type(rgf) :: rm2m
    !! A real grid function that stores \(r-2M\) everywhere.
  contains
    procedure :: init => tdc_init
    !! The initialization routine.
    procedure :: set_coefficients => tdc_set_coefficients
    !! The routine that sets the coefficients for the wave equation.
    procedure :: tdc_to_tortoise_cvec => tdc_tdc_to_tortoise_cvec
    !! Routine to transform from \(\lambda,\xi)\) to \((t,r_*)\) for complex
    !! vector arguments at the boundary of an element.
    procedure :: tdc_to_tortoise_cscal => tdc_tdc_to_tortoise_cscal
    !! Routine to transform from \(\lambda,\xi)\) to \((t,r_*)\) for complex
    !! scalar arguments at the boundary of an element.
    procedure :: tdc_to_tortoise_rscal => tdc_tdc_to_tortoise_rscal
    !! Routine to transform from \(\lambda,\xi)\) to \((t,r_*)\) for real
    !! scalar arguments at the boundary of an element.
    generic :: tdc_to_tortoise => tdc_to_tortoise_cvec, tdc_to_tortoise_cscal, &
                                  tdc_to_tortoise_rscal
    !! Generic name for routines that transform from \(\lambda,\xi)\) to
    !! \((t,r_*)\) at the boundary of an element.
    procedure :: tortoise_to_tdc_cvecb => tdc_tortoise_to_tdc_cvecb
    !! Routine to transform from \((t,r_*)\) to \(\lambda,\xi)\) for complex
    !! vector arguments at the boundary of an element.
    procedure :: tortoise_to_tdc_cscalb => tdc_tortoise_to_tdc_cscalb
    !! Routine to transform from \((t,r_*)\) to \(\lambda,\xi)\) for complex
    !! scalar arguments at the boundary of an element.
    procedure :: tortoise_to_tdc_cscal => tdc_tortoise_to_tdc_cscal
    !! Routine to transform from \((t,r_*)\) to \(\lambda,\xi)\) for complex
    !! scalar arguments at any node in any element.
    generic :: tortoise_to_tdc => tortoise_to_tdc_cvecb, &
                                  tortoise_to_tdc_cscalb, &
                                  tortoise_to_tdc_cscal
    !! Generic name for routines that transform from \((t,r_*)\) to
    !! \(\lambda,\xi)\).
  end type tdc