cpde_equation Derived Type

type, public, abstract, extends(equation) :: cpde_equation

A class derived from equation specific for PDE equations.


Inherits

type~~cpde_equation~~InheritsGraph type~cpde_equation cpde_equation type~cgf_pointer cgf_pointer type~cpde_equation->type~cgf_pointer data_pointer type~cgf cgf type~cpde_equation->type~cgf eq_data, eq_rhs_data, eq_tmp_data type~equation equation type~cpde_equation->type~equation type~cgf_pointer->type~cgf p type~gf_pointer gf_pointer type~cgf_pointer->type~gf_pointer type~gf gf type~cgf->type~gf type~element_cdata element_cdata type~cgf->type~element_cdata elems type~element_data element_data type~element_cdata->type~element_data

Inherited by

type~~cpde_equation~~InheritedByGraph type~cpde_equation cpde_equation type~scal_schw scal_schw type~scal_schw->type~cpde_equation type~sf_observer sf_observer type~sf_observer->type~scal_schw p

Contents

Source Code


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.


Type-Bound Procedures

procedure(cpde_eq_init_interface), public, deferred, pass :: init

The init routine is deferred.

  • subroutine cpde_eq_init_interface(this) Prototype

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

    Arguments

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

    The equation that is being initialized.

procedure(cpde_eq_rhs_interface), public, deferred, pass :: rhs

The rhs routine is deferred.

  • subroutine cpde_eq_rhs_interface(this) Prototype

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

    Arguments

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

    The equation for which the RHS is calculated.

procedure, public :: set_to_zero => cpde_set_to_zero

The set_to_zero routine is provided by cpde_set_to_zero.

  • interface

    public module subroutine cpde_set_to_zero(this, dest)

    The interface for the PDE version of set_to_zero. This interface is consistent with eq_set_to_zero_interface.

    Arguments

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

    The routine is called on this equation.

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

    Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

procedure, public :: update_vars => cpde_update_vars

The update_vars routine is provided by cpde_update_vars.

  • interface

    public module subroutine cpde_update_vars(this, source, dest, source2, scalar, scalar2)

    The interface for the PDE version of update_vars. This interface is consistent with eq_update_vars_interface.

    Arguments

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

    The routine is called on this equation.

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

    The first source for the update. Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

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

    The destination for the update. Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

    integer(kind=ip), intent(in), optional :: source2

    The second source for the update. Can be either -1 (RHS), 0 (main) or between 1 and ntmp (temporary).

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

    The scalar multiplying the first source.

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

    The scalar multiplying the second source.

procedure(cpde_eq_save_globals_1), public, deferred, pass :: save_globals_1

The save_globals_1 routine is deferred.

  • subroutine cpde_eq_save_globals_1(this) Prototype

    The interface for the PDE version of save_globals_1. This interface is consistent with eq_save_globals_1.

    Arguments

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

    The routine is called on this equation.

procedure(cpde_eq_save_globals_2), public, deferred, pass :: save_globals_2

The save_globals_2 routine is deferred.

  • subroutine cpde_eq_save_globals_2(this) Prototype

    The interface for the PDE version of save_globals_2. This interface is consistent with eq_save_globals_2.

    Arguments

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

    The routine is called on this equation.

procedure(cpde_eq_load_globals), public, deferred, pass :: load_globals

The load_globals routine is deferred.

  • subroutine cpde_eq_load_globals(this) Prototype

    The interface for the PDE version of load_globals. This interface is consistent with eq_load_globals.

    Arguments

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

    The routine is called on this equation.

procedure, public :: output => cpde_output

The output routine is provided by cpde_output.

  • interface

    public module subroutine cpde_output(this)

    The interface for the PDE version of output. This interface is consistent with eq_output.

    Arguments

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

    The routine is called on this equation.

procedure, public :: print_data => cpde_print_data

The print_data routine is provided by cpde_print_data.

  • interface

    public module subroutine cpde_print_data(this)

    The interface for the PDE version of print_data. This interface is consistent with eq_print_data.

    Arguments

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

    The routine is called on this equation.

Source Code

  type, abstract, extends(equation) :: cpde_equation
  !! A class derived from [[equation]] specific for PDE equations.
    integer(ip) :: 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(ip) :: 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), 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), 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), 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), 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:[[equation:ntmp]]) for the equation system.
    !! Should probably be changed to a 2d array to make this independent of
    !! spherical harmonic decomposition.
  contains 
    procedure (cpde_eq_init_interface), deferred, pass :: init
    !! The [[equation:init]] routine is deferred.
    procedure (cpde_eq_rhs_interface), deferred, pass :: rhs
    !! The [[equation:rhs]] routine is deferred.
    procedure :: set_to_zero => cpde_set_to_zero
    !! The [[equation:set_to_zero]] routine is provided by
    !! [[cpde_set_to_zero]].
    procedure :: update_vars => cpde_update_vars
    !! The [[equation:update_vars]] routine is provided by
    !! [[cpde_update_vars]].
    procedure (cpde_eq_save_globals_1), deferred, pass :: save_globals_1
    !! The [[equation:save_globals_1]] routine is deferred.
    procedure (cpde_eq_save_globals_2), deferred, pass :: save_globals_2
    !! The [[equation:save_globals_2]] routine is deferred.
    procedure (cpde_eq_load_globals), deferred, pass :: load_globals
    !! The [[equation:load_globals]] routine is deferred.
    procedure :: output => cpde_output
    !! The [[equation:output]] routine is provided by [[cpde_output]].
    procedure :: print_data => cpde_print_data
    !! The [[equation:print_data]] routine is provided by [[cpde_print_data]].
  end type cpde_equation