stdlib_specialmatrices Module

Provides derived-types and associated specialized linear algebra drivers for highly-structured matrices commonly encountered in the discretization of partial differential equations, as well as control and signal processing applications. (Specifications)


Used by


Interfaces

public interface dense

This interface provides methods to convert a matrix of one of the types defined by stdlib_specialmatrices to a standard rank-2 array. (Specifications)

  • private pure module function tridiagonal_to_dense_cdp(A) result(B)

    Convert a tridiagonal matrix to its dense representation.

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_cdp_type), intent(in) :: A

    Input Tridiagonal matrix.

    Return Value complex(kind=dp), allocatable, (:,:)

    Corresponding dense matrix.

  • private pure module function tridiagonal_to_dense_csp(A) result(B)

    Convert a tridiagonal matrix to its dense representation.

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_csp_type), intent(in) :: A

    Input Tridiagonal matrix.

    Return Value complex(kind=sp), allocatable, (:,:)

    Corresponding dense matrix.

  • private pure module function tridiagonal_to_dense_dp(A) result(B)

    Convert a tridiagonal matrix to its dense representation.

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_dp_type), intent(in) :: A

    Input Tridiagonal matrix.

    Return Value real(kind=dp), allocatable, (:,:)

    Corresponding dense matrix.

  • private pure module function tridiagonal_to_dense_sp(A) result(B)

    Convert a tridiagonal matrix to its dense representation.

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_sp_type), intent(in) :: A

    Input Tridiagonal matrix.

    Return Value real(kind=sp), allocatable, (:,:)

    Corresponding dense matrix.

public interface hermitian

This interface provides methods to compute the hermitian operation for the different matrix types defined by stdlib_specialmatrices. For real-valued matrices, this is equivalent to the standard transpose. Specifications

  • private pure module function hermitian_tridiagonal_cdp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_cdp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_cdp_type)

  • private pure module function hermitian_tridiagonal_csp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_csp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_csp_type)

  • private pure module function hermitian_tridiagonal_dp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_dp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_dp_type)

  • private pure module function hermitian_tridiagonal_sp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_sp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_sp_type)

public interface operator(*)

Overload the * for scalar-matrix multiplications for the different matrix types provided by stdlib_specialmatrices. Specifications

  • private pure module function scalar_multiplication_bis_tridiagonal_cdp(A, alpha) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_cdp_type), intent(in) :: A
    complex(kind=dp), intent(in) :: alpha

    Return Value type(tridiagonal_cdp_type)

  • private pure module function scalar_multiplication_bis_tridiagonal_csp(A, alpha) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_csp_type), intent(in) :: A
    complex(kind=sp), intent(in) :: alpha

    Return Value type(tridiagonal_csp_type)

  • private pure module function scalar_multiplication_bis_tridiagonal_dp(A, alpha) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_dp_type), intent(in) :: A
    real(kind=dp), intent(in) :: alpha

    Return Value type(tridiagonal_dp_type)

  • private pure module function scalar_multiplication_bis_tridiagonal_sp(A, alpha) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_sp_type), intent(in) :: A
    real(kind=sp), intent(in) :: alpha

    Return Value type(tridiagonal_sp_type)

  • private pure module function scalar_multiplication_tridiagonal_cdp(alpha, A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: alpha
    type(tridiagonal_cdp_type), intent(in) :: A

    Return Value type(tridiagonal_cdp_type)

  • private pure module function scalar_multiplication_tridiagonal_csp(alpha, A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: alpha
    type(tridiagonal_csp_type), intent(in) :: A

    Return Value type(tridiagonal_csp_type)

  • private pure module function scalar_multiplication_tridiagonal_dp(alpha, A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: alpha
    type(tridiagonal_dp_type), intent(in) :: A

    Return Value type(tridiagonal_dp_type)

  • private pure module function scalar_multiplication_tridiagonal_sp(alpha, A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: alpha
    type(tridiagonal_sp_type), intent(in) :: A

    Return Value type(tridiagonal_sp_type)

public interface operator(+)

Overload the + operator for matrix-matrix addition. The two matrices need to be of the same type and kind. Specifications

public interface operator(-)

Overload the - operator for matrix-matrix subtraction. The two matrices need to be of the same type and kind. Specifications

public interface spmv

(Specifications) This interface provides methods to compute the matrix-vector product

for the different matrix types defined by stdlib_specialmatrices.

  • private module subroutine spmv_tridiag_1d_cdp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_cdp_type), intent(in) :: A
    complex(kind=dp), intent(in), contiguous, target :: x(:)
    complex(kind=dp), intent(inout), contiguous, target :: y(:)
    real(kind=dp), intent(in), optional :: alpha
    real(kind=dp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op
  • private module subroutine spmv_tridiag_1d_csp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_csp_type), intent(in) :: A
    complex(kind=sp), intent(in), contiguous, target :: x(:)
    complex(kind=sp), intent(inout), contiguous, target :: y(:)
    real(kind=sp), intent(in), optional :: alpha
    real(kind=sp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op
  • private module subroutine spmv_tridiag_1d_dp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_dp_type), intent(in) :: A
    real(kind=dp), intent(in), contiguous, target :: x(:)
    real(kind=dp), intent(inout), contiguous, target :: y(:)
    real(kind=dp), intent(in), optional :: alpha
    real(kind=dp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op
  • private module subroutine spmv_tridiag_1d_sp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_sp_type), intent(in) :: A
    real(kind=sp), intent(in), contiguous, target :: x(:)
    real(kind=sp), intent(inout), contiguous, target :: y(:)
    real(kind=sp), intent(in), optional :: alpha
    real(kind=sp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op
  • private module subroutine spmv_tridiag_2d_cdp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_cdp_type), intent(in) :: A
    complex(kind=dp), intent(in), contiguous, target :: x(:,:)
    complex(kind=dp), intent(inout), contiguous, target :: y(:,:)
    real(kind=dp), intent(in), optional :: alpha
    real(kind=dp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op
  • private module subroutine spmv_tridiag_2d_csp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_csp_type), intent(in) :: A
    complex(kind=sp), intent(in), contiguous, target :: x(:,:)
    complex(kind=sp), intent(inout), contiguous, target :: y(:,:)
    real(kind=sp), intent(in), optional :: alpha
    real(kind=sp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op
  • private module subroutine spmv_tridiag_2d_dp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_dp_type), intent(in) :: A
    real(kind=dp), intent(in), contiguous, target :: x(:,:)
    real(kind=dp), intent(inout), contiguous, target :: y(:,:)
    real(kind=dp), intent(in), optional :: alpha
    real(kind=dp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op
  • private module subroutine spmv_tridiag_2d_sp(A, x, y, alpha, beta, op)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_sp_type), intent(in) :: A
    real(kind=sp), intent(in), contiguous, target :: x(:,:)
    real(kind=sp), intent(inout), contiguous, target :: y(:,:)
    real(kind=sp), intent(in), optional :: alpha
    real(kind=sp), intent(in), optional :: beta
    character(len=1), intent(in), optional :: op

public interface transpose

This interface provides methods to compute the transpose operation for the different matrix types defined by stdlib_specialmatrices. Specifications

  • private pure module function transpose_tridiagonal_cdp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_cdp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_cdp_type)

  • private pure module function transpose_tridiagonal_csp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_csp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_csp_type)

  • private pure module function transpose_tridiagonal_dp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_dp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_dp_type)

  • private pure module function transpose_tridiagonal_sp(A) result(B)

    Arguments

    Type IntentOptional Attributes Name
    type(tridiagonal_sp_type), intent(in) :: A

    Input matrix.

    Return Value type(tridiagonal_sp_type)

public interface tridiagonal

(Specifications) This interface provides different methods to construct a tridiagonal matrix. Only the non-zero elements of are stored, i.e.

Syntax

  • Construct a real tridiagonal matrix from rank-1 arrays:
   integer, parameter :: n
   real(dp), allocatable :: dl(:), dv(:), du(:)
   type(tridiagonal_rdp_type) :: A
   integer :: i

   dl = [(i, i=1, n-1)]; dv = [(2*i, i=1, n)]; du = [(3*i, i=1, n)]
   A = Tridiagonal(dl, dv, du)
  • Construct a real tridiagonal matrix with constant diagonals:
   integer, parameter :: n
   real(dp), parameter :: a = 1.0_dp, b = 1.0_dp, c = 2.0_dp
   type(tridiagonal_rdp_type) :: A

   A = Tridiagonal(a, b, c, n)
  • private module function initialize_constant_tridiagonal_impure_cdp(dl, dv, du, n, err) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: dl

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: dv

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_cdp_type)

    Corresponding Tridiagonal matrix.

  • private module function initialize_constant_tridiagonal_impure_csp(dl, dv, du, n, err) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: dl

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: dv

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_csp_type)

    Corresponding Tridiagonal matrix.

  • private module function initialize_constant_tridiagonal_impure_dp(dl, dv, du, n, err) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: dl

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: dv

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_dp_type)

    Corresponding Tridiagonal matrix.

  • private module function initialize_constant_tridiagonal_impure_sp(dl, dv, du, n, err) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: dl

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: dv

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_sp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_constant_tridiagonal_pure_cdp(dl, dv, du, n) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: dl

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: dv

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    Return Value type(tridiagonal_cdp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_constant_tridiagonal_pure_csp(dl, dv, du, n) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: dl

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: dv

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    Return Value type(tridiagonal_csp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_constant_tridiagonal_pure_dp(dl, dv, du, n) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: dl

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: dv

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    Return Value type(tridiagonal_dp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_constant_tridiagonal_pure_sp(dl, dv, du, n) result(A)

    Construct a tridiagonal matrix with constant elements.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: dl

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: dv

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: du

    Tridiagonal matrix elements.

    integer(kind=ilp), intent(in) :: n

    Matrix dimension.

    Return Value type(tridiagonal_sp_type)

    Corresponding Tridiagonal matrix.

  • private module function initialize_tridiagonal_impure_cdp(dl, dv, du, err) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_cdp_type)

    Corresponding Tridiagonal matrix.

  • private module function initialize_tridiagonal_impure_csp(dl, dv, du, err) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_csp_type)

    Corresponding Tridiagonal matrix.

  • private module function initialize_tridiagonal_impure_dp(dl, dv, du, err) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_dp_type)

    Corresponding Tridiagonal matrix.

  • private module function initialize_tridiagonal_impure_sp(dl, dv, du, err) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    type(linalg_state_type), intent(out) :: err

    Error handling.

    Return Value type(tridiagonal_sp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_tridiagonal_pure_cdp(dl, dv, du) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    complex(kind=dp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    Return Value type(tridiagonal_cdp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_tridiagonal_pure_csp(dl, dv, du) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    complex(kind=sp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    Return Value type(tridiagonal_csp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_tridiagonal_pure_dp(dl, dv, du) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    real(kind=dp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    Return Value type(tridiagonal_dp_type)

    Corresponding Tridiagonal matrix.

  • private pure module function initialize_tridiagonal_pure_sp(dl, dv, du) result(A)

    Construct a tridiagonal matrix from the rank-1 arrays dl, dv and du.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: dl(:)

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: dv(:)

    Tridiagonal matrix elements.

    real(kind=sp), intent(in) :: du(:)

    Tridiagonal matrix elements.

    Return Value type(tridiagonal_sp_type)

    Corresponding Tridiagonal matrix.


Derived Types

type, public ::  tridiagonal_cdp_type

Base type to define a tridiagonal matrix.

type, public ::  tridiagonal_csp_type

Base type to define a tridiagonal matrix.

type, public ::  tridiagonal_dp_type

Base type to define a tridiagonal matrix.

type, public ::  tridiagonal_sp_type

Base type to define a tridiagonal matrix.