grid_function Module

Module that defines the concept of a grid function and the interface of the associated routines.

The implementation is found in submodule_grid_function_implementation.f90.


Uses

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

Used by

  • module~~grid_function~~UsedByGraph module~grid_function grid_function module~world_tube world_tube module~world_tube->module~grid_function module~effective_source effective_source module~effective_source->module~grid_function module~effective_source->module~world_tube module~grid grid module~grid->module~grid_function module~observers observers module~observers->module~grid_function module~scalar_schw scalar_schw module~scalar_schw->module~grid_function module~time_dependent_coordinate time_dependent_coordinate module~scalar_schw->module~time_dependent_coordinate module~pde_equations pde_equations module~scalar_schw->module~pde_equations module~scalar_schw_eff scalar_schw_eff module~scalar_schw->module~scalar_schw_eff module~time_dependent_coordinate->module~grid_function module~grid_function_implementation grid_function_implementation module~grid_function_implementation->module~grid_function module~pde_equations->module~grid_function proc~get_elem_flux get_elem_flux proc~get_elem_flux->module~grid_function proc~get_elem_flux->module~world_tube proc~get_elem_flux->module~grid module~scalar_schw_eff->module~effective_source proc~scal_schw_eff_init scal_schw_eff_init proc~scal_schw_eff_init->module~scalar_schw proc~output_coords output_coords proc~output_coords->module~grid module~grid_implementation grid_implementation module~grid_implementation->module~grid program~test test program~test->module~world_tube program~test->module~grid program~test->module~observers program~test->module~scalar_schw program~test->module~scalar_schw_eff module~singular_observer singular_observer program~test->module~singular_observer module~self_force_observer self_force_observer program~test->module~self_force_observer proc~read_all_modes read_all_modes proc~read_all_modes->module~world_tube proc~read_all_modes->module~grid proc~scal_schw_rhs scal_schw_rhs proc~scal_schw_rhs->module~world_tube proc~scal_schw_rhs->module~grid proc~scal_schw_init scal_schw_init proc~scal_schw_init->module~grid proc~sobs_init sobs_init proc~sobs_init->module~effective_source proc~sobs_init->module~grid module~singular_observer->module~effective_source module~singular_observer->module~observers module~pde_equations_implementation pde_equations_implementation module~pde_equations_implementation->module~pde_equations module~observers_implementation observers_implementation module~observers_implementation->module~observers proc~tdc_set_coefficients tdc_set_coefficients proc~tdc_set_coefficients->module~grid module~scalar_schw_implementation scalar_schw_implementation module~scalar_schw_implementation->module~scalar_schw module~world_tube_implementation world_tube_implementation module~world_tube_implementation->module~world_tube proc~scal_schw_load_globals scal_schw_load_globals proc~scal_schw_load_globals->module~grid module~time_dependent_coordinate_implementation time_dependent_coordinate_implementation module~time_dependent_coordinate_implementation->module~time_dependent_coordinate module~self_force_observer->module~observers module~self_force_observer->module~scalar_schw module~singuler_observer_implementation singuler_observer_implementation module~singuler_observer_implementation->module~singular_observer module~scalar_schw_eff_implementation scalar_schw_eff_implementation module~scalar_schw_eff_implementation->module~scalar_schw_eff 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

public interface rgf

The constructor for a real data type grid function.

  • public interface init_rgf()

    Arguments

    None

public interface cgf

The constructor for a complex data type grid function.

  • public interface init_cgf()

    Arguments

    None

public interface igfb

The constructor for an integer data type boundary grid function.

  • public interface init_igfb()

    Arguments

    None

public interface rgfb

The constructor for a real data type boundary grid function.

  • public interface init_rgfb()

    Arguments

    None

public interface cgfb

The constructor for a complex data type boundary grid function.

  • public interface init_cgfb()

    Arguments

    None

interface

  • public module function init_rgf(n, order, var_name)

    The interface for a constructor for a real data type grid function.

    Arguments

    Type IntentOptional AttributesName
    integer(kind=ip), intent(in) :: n

    The number of elements in this grid function.

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

    The order of the elements in this grid function.

    character(len=*), intent(in) :: var_name

    The name to be assigned to this grid function.

    Return Value type(rgf)

    The return type has to be of type rgf.

interface

  • public module function init_cgf(n, order, var_name)

    The interface for a constructor for a complex data type grid function.

    Arguments

    Type IntentOptional AttributesName
    integer(kind=ip), intent(in) :: n

    The number of elements in this grid function.

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

    The order of the elements in this grid function.

    character(len=*), intent(in) :: var_name

    The name to be assigned to this grid function.

    Return Value type(cgf)

    The return type has to be of type cgf.

interface

  • public module function init_igfb(n, var_name)

    The interface for a constructor for an integer data type boundary grid function.

    Arguments

    Type IntentOptional AttributesName
    integer(kind=ip), intent(in) :: n

    The number of elements.

    character(len=*), intent(in) :: var_name

    The name of the object.

    Return Value type(igfb)

    The object to construct.

interface

  • public module function init_rgfb(n, var_name)

    The interface for a constructor for a real data type boundary grid function.

    Arguments

    Type IntentOptional AttributesName
    integer(kind=ip), intent(in) :: n

    The number of elements.

    character(len=*), intent(in) :: var_name

    The name of the object.

    Return Value type(rgfb)

    The object to construct.

interface

  • public module function init_cgfb(n, var_name)

    The interface for a constructor for a complex data type boundary grid function.

    Arguments

    Type IntentOptional AttributesName
    integer(kind=ip), intent(in) :: n

    The number of elements.

    character(len=*), intent(in) :: var_name

    The name of the object.

    Return Value type(cgfb)

    The object to construct.

interface

  • public module subroutine output_rgf(this, coord)

    The interface for an output routine for a real data type grid function.

    Arguments

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

    Has to be called with an rgf class.

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

    A real grid function that contains the coordinates.

interface

  • public module subroutine deallocate_rgf(this)

    The interface for a finalize for a real data type grid function.

    Arguments

    Type IntentOptional AttributesName
    type(rgf) :: this

    Has to be called with an rgf class.

interface

  • public module subroutine output_cgf(this, coord)

    The interface for an output routine for a complex data type grid function.

    Arguments

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

    Has to be called with an cgf class.

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

    A real grid function that contains the coordinates.

interface

  • public module subroutine copy_cgf(this, gf)

    The interface for a procedure for copying the data from one complex grid function to another.

    Read more…

    Arguments

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

    The routine is called on this object.

    class(cgf), intent(in) :: gf

    The grid function to copy.

interface

  • public module subroutine zero_cgf(this)

    The interface for a procedure for setting a complex grid function to zero.

    Read more…

    Arguments

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

    The routine is called on this object.

interface

  • public module subroutine mult_sc_cgf(this, scalar)

    The interface for a procedure for multplying a complex grid function with a real scalar.

    Read more…

    Arguments

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

    The routine is called on this object.

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

    The scalar to multiply with.

interface

  • public module subroutine sc_mult_gf_cgf(this, scalar, gf)

    The interface for a procedure for multplying a complex grid function with a real scalar and storing the result in another complex grid function.

    Read more…

    Arguments

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

    The routine is called on this object.

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

    The scalar to multiply with.

    class(cgf), intent(in) :: gf

    The grid function to multiply with.

interface

  • public module subroutine add_gf_cgf(this, gf)

    The interface for a procedure for adding 2 complex grid functions together and storing the result in the first one.

    Read more…

    Arguments

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

    The routine is called on this object.

    class(cgf), intent(in) :: gf

    The grid function to add.

interface

  • public module subroutine add_sc_mult_gf_cgf(this, scalar, gf)

    The interface for a procedure adding together a grid function and a scalar multiplying another grid function and storing the result in the first one.

    Read more…

    Arguments

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

    The routine is called on this object.

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

    The scalar to multiply with.

    class(cgf), intent(in) :: gf

    The second grid function.

interface

  • public module subroutine mult_sc_add_sc_mult_gf_cgf(this, scalar1, scalar2, gf)

    The interface for a procedure for adding together a scalar multiplying a grid function with another scalar multiplying another grid function and storing the result in the first one.

    Read more…

    Arguments

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

    The routine is called on this object.

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

    The first scalar.

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

    The second scalar.

    class(cgf), intent(in) :: gf

    The second grid function.

interface

  • public module subroutine gf1_plus_sc_mult_gf2_cgf(this, gf1, scalar, gf2)

    The interface for a procedure for storing the result of adding a second grid function with a scalar multiplying a third grid function in a grid function.

    Read more…

    Arguments

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

    The routine is called on this object.

    class(cgf), intent(in) :: gf1

    The second grid function.

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

    The scalar.

    class(cgf), intent(in) :: gf2

    The third grid function.

interface

  • public module subroutine sc_mult_gf1_plus_sc_mult_gf2_cgf(this, gf1, scalar1, gf2, scalar2)

    The interface for a procedure for storing the result of adding a scalar multiplying a second grid function with another scalar multiplying a third grid function in a grid function.

    Read more…

    Arguments

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

    The routine is called on this object.

    class(cgf), intent(in) :: gf1

    The second grid function.

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

    The first scalar.

    class(cgf), intent(in) :: gf2

    The third grid function.

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

    The second scalar.

interface

  • public module subroutine deallocate_cgf(this)

    The interface for a finalizer for a complex data type grid function.

    Arguments

    Type IntentOptional AttributesName
    type(cgf) :: this

    The object to finalize

interface

  • public module subroutine output_igfb(this, coord)

    The interface for an output routine for an integer data type boundary grid function.

    Arguments

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

    The routine is called on this object.

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

    A real grid function that contains the coordinates.

interface

  • public module subroutine deallocate_igfb(this)

    The interface for a finalizer for an integer data type boundary grid function.

    Arguments

    Type IntentOptional AttributesName
    type(igfb) :: this

    The object to finalize.

interface

  • public module subroutine output_rgfb(this, coord)

    The interface for an output routine for a real data type boundary grid function.

    Arguments

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

    The routine is called on this object.

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

    A real grid function that contains the coordinates.

interface

  • public module subroutine deallocate_rgfb(this)

    The interface for a finalizer for a real data type boundary grid function.

    Arguments

    Type IntentOptional AttributesName
    type(rgfb) :: this

    The object to finalize.

interface

  • public module subroutine output_cgfb(this, coord)

    The interface for an output routine for a complex data type boundary grid function.

    Arguments

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

    The routine is called on this object.

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

    A real grid function that contains the coordinates.

interface

  • public module subroutine deallocate_cgfb(this)

    The interface for a finalizer for a complex data type boundary grid function.

    Arguments

    Type IntentOptional AttributesName
    type(cgfb) :: this

    The object to finalize.


Derived Types

type, public, abstract :: gf

An abstract grid function class.

Components

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

The number of elements.

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

The name of the grid function.

integer(kind=ip), public :: io_id

The file unit used for output of this grid function.

type, public, extends(gf) :: rgf

A real data instance of the abstract grid function class. Note this is not complete, as it has not been needed for evolution yet.

Components

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

The number of elements.

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

The name of the grid function.

integer(kind=ip), public :: io_id

The file unit used for output of this grid function.

type(element_rdata), public, dimension(:), allocatable:: elems

A 1d array of the real element data class.

Constructor

The constructor for a real data type grid function.

public interface init_rgf()

Finalizations Procedures

final :: deallocate_rgf

The finalizer.

Type-Bound Procedures

procedure, public, non_overridable :: output => output_rgf

Generic type bound procedure for output.

type, public, extends(gf) :: cgf

A complex data instance of the abstract grid function class.

Components

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

The number of elements.

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

The name of the grid function.

integer(kind=ip), public :: io_id

The file unit used for output of this grid function.

type(element_cdata), public, dimension(:), allocatable:: elems

A 1d array of the complex element data class.

Constructor

The constructor for a complex data type grid function.

public interface init_cgf()

Finalizations Procedures

final :: deallocate_cgf

The finalizer.

Type-Bound Procedures

procedure, public, non_overridable :: output => output_cgf

Generic type bound procedure for output.

procedure, public, non_overridable :: copy => copy_cgf

Generic type bound procedure for copying the data from one complex grid function to another.

procedure, public, non_overridable :: zero => zero_cgf

Generic type bound procedure for setting a complex grid function to zero.

procedure, public, non_overridable :: mult_sc => mult_sc_cgf

Generic type bound procedure for multplying a complex grid function with a real scalar.

procedure, public, non_overridable :: sc_mult_gf => sc_mult_gf_cgf

Generic type bound procedure for multplying a complex grid function with a real scalar and storing the result in another complex grid function.

procedure, public, non_overridable :: add_gf => add_gf_cgf

Generic type bound procedure for adding 2 complex grid functions together and storing the result in the first one.

procedure, public, non_overridable :: add_sc_mult_gf => add_sc_mult_gf_cgf

Generic type bound procedure adding together a grid function and a scalar multiplying another grid function and storing the result in the first one.

procedure, public, non_overridable :: mult_sc_add_sc_mult_gf => mult_sc_add_sc_mult_gf_cgf

Generic type bound procedure for adding together a scalar multiplying a grid function with another scalar multiplying another grid function and storing the result in the first one.

procedure, public, non_overridable :: gf1_plus_sc_mult_gf2 => gf1_plus_sc_mult_gf2_cgf

Generic type bound procedure for storing the result of adding a second grid function with a scalar multiplying a third grid function in a grid function.

procedure, public, non_overridable :: sc_mult_gf1_plus_sc_mult_gf2 => sc_mult_gf1_plus_sc_mult_gf2_cgf

Generic type bound procedure for storing the result of adding a scalar multiplying a second grid function with another scalar multiplying a third grid function in a grid function.

type, public, abstract :: gf_pointer

An abstract class of a pointer to a grid function.

type, public, extends(gf_pointer) :: rgf_pointer

A real data type instance of a pointer to a grid function class.

Components

TypeVisibility AttributesNameInitial
class(rgf), public, pointer:: p

The pointer to a real grid function.

type, public, extends(gf_pointer) :: cgf_pointer

A complex data type instance of a pointer to a grid function class.

Components

TypeVisibility AttributesNameInitial
class(cgf), public, pointer:: p

The pointer to a complex grid function.

type, public, abstract :: gfb

An abstract class of a grid function of element boundary data.

Components

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

The number of elements in the grid function.

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

The name of the boundary data.

integer(kind=ip), public :: iob_id

The file unit used for output of this object.

type, public, extends(gfb) :: igfb

An integer data type instance of a boundary grid funcion class.

Components

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

The number of elements in the grid function.

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

The name of the boundary data.

integer(kind=ip), public :: iob_id

The file unit used for output of this object.

type(element_boundary_idata), public, dimension(:), allocatable:: elems

A 1d array of element_boundary_idata type.

Constructor

The constructor for an integer data type boundary grid function.

public interface init_igfb()

Finalizations Procedures

final :: deallocate_igfb

The finalizer.

Type-Bound Procedures

procedure, public, non_overridable :: output => output_igfb

Generic type bound procedure for output.

type, public, extends(gfb) :: rgfb

A real data type instance of a boundary grid funcion class.

Components

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

The number of elements in the grid function.

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

The name of the boundary data.

integer(kind=ip), public :: iob_id

The file unit used for output of this object.

type(element_boundary_rdata), public, dimension(:), allocatable:: elems

A 1d array of element_boundary_rdata type.

Constructor

The constructor for a real data type boundary grid function.

public interface init_rgfb()

Finalizations Procedures

final :: deallocate_rgfb

The finalizer.

Type-Bound Procedures

procedure, public, non_overridable :: output => output_rgfb

Generic type bound procedure for output.

type, public, extends(gfb) :: cgfb

A complex data type instance of a boundary grid funcion class.

Components

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

The number of elements in the grid function.

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

The name of the boundary data.

integer(kind=ip), public :: iob_id

The file unit used for output of this object.

type(element_boundary_cdata), public, dimension(:), allocatable:: elems

A 1d array of element_boundary_cdata type.

Constructor

The constructor for a complex data type boundary grid function.

public interface init_cgfb()

Finalizations Procedures

final :: deallocate_cgfb

The finalizer.

Type-Bound Procedures

procedure, public, non_overridable :: output => output_cgfb

Generic type bound procedure for output.