fin_diff_block Derived Type

type, public :: fin_diff_block

A data type representing a matrix finite difference operator. It can be useful when preconditioning systems which use a spectral discretisation. It is inherently 1-D in its implementation. Note that multiplication of a field will simply call that field's differentiation operator, which may or may not use a finite difference method.

When constructing an instance of this type, a template field must be passed which has the same grid as any other fields which will be operated upon. Additionally, types and locations of boundary conditions must be passed.


Contents

Source Code


Components

TypeVisibility AttributesNameInitial
real(kind=r8), private, dimension(:), allocatable:: diagonal

The diagonal of the tridiagonal matrix representation of this block.

real(kind=r8), private, dimension(:), allocatable:: super_diagonal

The super-diagonal of the tridiagonal matrix representation of this block.

real(kind=r8), private, dimension(:), allocatable:: sub_diagonal

The sub-diagonal of the tridiagonal matrix representation of this block.

real(kind=r8), private, dimension(:), allocatable:: l_multipliers

Multipliers defining the L matrix in the LU factorisation of the tridiagonal matrix representation of this block.

real(kind=r8), private, dimension(:), allocatable:: u_diagonal

The diagonal of the U matrix in the LU factorisation of the tridiagonal matrix representation of this block.

real(kind=r8), private, dimension(:), allocatable:: u_superdiagonal1

The first superdiagonal of the U matrix in the LU factorisation of the tridiagonal matrix representation of this block.

real(kind=r8), private, dimension(:), allocatable:: u_superdiagonal2

The second superdiagonal of the U matrix in the LU factorisation of the tridiagonal matrix representation of this block.

integer, private, dimension(:), allocatable:: pivots

Pivot indicies from the LU factorisation of the tridiagonal matrix representation of this block.

integer, private, dimension(:), allocatable:: boundary_locs

Locations in the raw arrays which are used to specify boundary conditions.

integer, private, dimension(:), allocatable:: boundary_types

The types of boundary conditions, specified using the parameters found in boundary_types_mod.

logical, private :: had_offset =.true.

True if the factorisation was computed from a tridiagonal system in which an offset was added to the diagonal.


Constructor

public interface fin_diff_block

  • private function constructor(template, boundary_locs, boundary_types) result(this)

    Author
    Chris MacMackin
    Date
    December 2016

    Build a tridiagonal matrix block for finite differences. See the end of the documentation of the fin_diff_block type for a description of how boundary conditions are treated.

    Arguments

    Type IntentOptional AttributesName
    class(abstract_field), intent(in) :: template

    A scalar field with the same grid as any fields passed as arguments to the solve_for method.

    integer, intent(in), optional dimension(:):: boundary_locs

    The locations in the raw representation of rhs for which boundary conditions are specified. Defaults to there being none.

    integer, intent(in), optional dimension(:):: boundary_types

    Integers specifying the type of boundary condition. The type of boundary condition corresponding to a given integer is specified in boundary_types_mod. Only Dirichlet and Neumann conditions are supported. Defaults to Dirichlet. The order in which they are stored must match that of boundary_locs.

    Return Value type(fin_diff_block)

    A new finite difference operator


Type-Bound Procedures

procedure, private :: fin_diff_block_solve_scalar

  • private function fin_diff_block_solve_scalar(this, rhs, offset) result(solution)

    Author
    Chris MacMackin
    Date
    December 2016

    Solves the linear(ised) system represented by this finite difference block, for a given right hand side state vector (represented by a scalar field). Optionally, the differential operator can be augmented by adding an offset, i.e. a scalar field which is added to the operator.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(fin_diff_block), intent(inout) :: this
    class(scalar_field), intent(in) :: rhs

    The right hand side of the linear(ised) system.

    class(scalar_field), intent(in), optional :: offset

    An offset to add to the differential operator

    Return Value class(scalar_field), pointer

procedure, private :: fin_diff_block_solve_vector

  • private function fin_diff_block_solve_vector(this, rhs, offset) result(solution)

    Author
    Chris MacMackin
    Date
    December 2016

    Solves the linear(ised) system represented by this finite difference block, for a given right hand side state vector (represented by a vector field). Optionally, the differential operator can be augmented by adding an offset, i.e. a vector field which is added to the operator.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(fin_diff_block), intent(inout) :: this
    class(cheb1d_vector_field), intent(in) :: rhs

    The right hand side of the linear(ised) system.

    class(cheb1d_vector_field), intent(in), optional :: offset

    An offset to add to the differential operator

    Return Value class(vector_field), pointer

  • private function fin_diff_block_solve_scalar(this, rhs, offset) result(solution)

    Author
    Chris MacMackin
    Date
    December 2016

    Solves the linear(ised) system represented by this finite difference block, for a given right hand side state vector (represented by a scalar field). Optionally, the differential operator can be augmented by adding an offset, i.e. a scalar field which is added to the operator.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(fin_diff_block), intent(inout) :: this
    class(scalar_field), intent(in) :: rhs

    The right hand side of the linear(ised) system.

    class(scalar_field), intent(in), optional :: offset

    An offset to add to the differential operator

    Return Value class(scalar_field), pointer

  • private function fin_diff_block_solve_vector(this, rhs, offset) result(solution)

    Author
    Chris MacMackin
    Date
    December 2016

    Solves the linear(ised) system represented by this finite difference block, for a given right hand side state vector (represented by a vector field). Optionally, the differential operator can be augmented by adding an offset, i.e. a vector field which is added to the operator.

    Read more…

    Arguments

    Type IntentOptional AttributesName
    class(fin_diff_block), intent(inout) :: this
    class(cheb1d_vector_field), intent(in) :: rhs

    The right hand side of the linear(ised) system.

    class(cheb1d_vector_field), intent(in), optional :: offset

    An offset to add to the differential operator

    Return Value class(vector_field), pointer

Source Code

  type, public :: fin_diff_block
    !* Author: Chris MacMackin
    !  Date: December 2016
    !
    ! A data type representing a matrix finite difference operator. It
    ! can be useful when preconditioning systems which use a spectral
    ! discretisation. It is inherently 1-D in its implementation. Note
    ! that multiplication of a field will simply call that field's
    ! differentiation operator, which may or may not use a finite
    ! difference method.
    !
    ! When constructing an instance of this type, a template field
    ! must be passed which has the same grid as any other fields which
    ! will be operated upon. Additionally, types and locations of
    ! boundary conditions must be passed.
    !
    private
    real(r8), dimension(:), allocatable :: diagonal
      !! The diagonal of the tridiagonal matrix representation of this
      !! block.
    real(r8), dimension(:), allocatable :: super_diagonal
      !! The super-diagonal of the tridiagonal matrix representation
      !! of this block.
    real(r8), dimension(:), allocatable :: sub_diagonal
      !! The sub-diagonal of the tridiagonal matrix representation of
      !! this block.
    real(r8), dimension(:), allocatable :: l_multipliers
      !! Multipliers defining the L matrix in the LU factorisation of
      !! the tridiagonal matrix representation of this block.
    real(r8), dimension(:), allocatable :: u_diagonal
      !! The diagonal of the U matrix in the LU factorisation of
      !! the tridiagonal matrix representation of this block.
    real(r8), dimension(:), allocatable :: u_superdiagonal1
      !! The first superdiagonal of the U matrix in the LU
      !! factorisation of the tridiagonal matrix representation of
      !! this block.
    real(r8), dimension(:), allocatable :: u_superdiagonal2
      !! The second superdiagonal of the U matrix in the LU
      !! factorisation of the tridiagonal matrix representation of
      !! this block.
    integer, dimension(:), allocatable  :: pivots
      !! Pivot indicies from the LU factorisation of the tridiagonal
      !! matrix representation of this block.
    integer, dimension(:), allocatable  :: boundary_locs
      !! Locations in the raw arrays which are used to specify
      !! boundary conditions.
    integer, dimension(:), allocatable  :: boundary_types
      !! The types of boundary conditions, specified using the
      !! parameters found in [[boundary_types_mod]].
    logical                             :: had_offset = .true.
      !! True if the factorisation was computed from a tridiagonal
      !! system in which an offset was added to the diagonal.
!    real(r8)                            :: magnitude
!      !! The norm of the superdiagonal of the matrix. If an iterative
!      !! method is used, this is needed to decide how to do so.
  contains
    private
    procedure :: fin_diff_block_solve_scalar
    procedure :: fin_diff_block_solve_vector
    generic, public :: solve_for => fin_diff_block_solve_scalar, &
                                    fin_diff_block_solve_vector
  end type fin_diff_block