stdlib_linalg Module

Provides a support for various linear algebra procedures (Specification)



Interfaces

public interface cross_product

Computes the cross product of two vectors, returning a rank-1 and size-3 array (Specification)

  • private pure module function cross_product_cdp(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: a(3)
    complex(kind=dp), intent(in) :: b(3)

    Return Value complex(kind=dp), (3)

  • private pure module function cross_product_csp(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: a(3)
    complex(kind=sp), intent(in) :: b(3)

    Return Value complex(kind=sp), (3)

  • private pure module function cross_product_iint16(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: a(3)
    integer(kind=int16), intent(in) :: b(3)

    Return Value integer(kind=int16), (3)

  • private pure module function cross_product_iint32(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: a(3)
    integer(kind=int32), intent(in) :: b(3)

    Return Value integer(kind=int32), (3)

  • private pure module function cross_product_iint64(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: a(3)
    integer(kind=int64), intent(in) :: b(3)

    Return Value integer(kind=int64), (3)

  • private pure module function cross_product_iint8(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: a(3)
    integer(kind=int8), intent(in) :: b(3)

    Return Value integer(kind=int8), (3)

  • private pure module function cross_product_rdp(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: a(3)
    real(kind=dp), intent(in) :: b(3)

    Return Value real(kind=dp), (3)

  • private pure module function cross_product_rsp(a, b) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: a(3)
    real(kind=sp), intent(in) :: b(3)

    Return Value real(kind=sp), (3)

public interface det

Computes the determinant of a square matrix (Specification)

Summary

Interface for computing matrix determinant.

Description

This interface provides methods for computing the determinant of a matrix. Supported data types include real and complex.

Note

The provided functions are intended for square matrices only.

Note

BLAS/LAPACK backends do not currently support extended precision (xdp).

Example

    real(sp) :: a(3,3), d
    type(linalg_state_type) :: state  
    a = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])

    ! ...
    d = det(a,err=state)
    if (state%ok()) then 
       print *, 'Success! det=',d
    else
       print *, state%print()
    endif
    ! ...
  • private interface stdlib_linalg_rspdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_pure_rspdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_rdpdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_pure_rdpdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_cspdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_pure_cspdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_cdpdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_pure_cdpdeterminant()

    Arguments

    None

public interface diag

Creates a diagonal array or extract the diagonal elements of an array (Specification)

  • private module function diag_cdp(v) result(res)

    Arguments

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

    Return Value complex(kind=dp), (size(v),size(v))

  • private module function diag_cdp_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value complex(kind=dp), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_cdp_mat(A) result(res)

    Arguments

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

    Return Value complex(kind=dp), (minval(shape(A)))

  • private module function diag_cdp_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value complex(kind=dp), (minval(shape(A))-abs(k))

  • private module function diag_csp(v) result(res)

    Arguments

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

    Return Value complex(kind=sp), (size(v),size(v))

  • private module function diag_csp_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value complex(kind=sp), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_csp_mat(A) result(res)

    Arguments

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

    Return Value complex(kind=sp), (minval(shape(A)))

  • private module function diag_csp_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value complex(kind=sp), (minval(shape(A))-abs(k))

  • private module function diag_iint16(v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: v(:)

    Return Value integer(kind=int16), (size(v),size(v))

  • private module function diag_iint16_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value integer(kind=int16), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_iint16_mat(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)

    Return Value integer(kind=int16), (minval(shape(A)))

  • private module function diag_iint16_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value integer(kind=int16), (minval(shape(A))-abs(k))

  • private module function diag_iint32(v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: v(:)

    Return Value integer(kind=int32), (size(v),size(v))

  • private module function diag_iint32_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value integer(kind=int32), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_iint32_mat(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)

    Return Value integer(kind=int32), (minval(shape(A)))

  • private module function diag_iint32_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value integer(kind=int32), (minval(shape(A))-abs(k))

  • private module function diag_iint64(v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: v(:)

    Return Value integer(kind=int64), (size(v),size(v))

  • private module function diag_iint64_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value integer(kind=int64), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_iint64_mat(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)

    Return Value integer(kind=int64), (minval(shape(A)))

  • private module function diag_iint64_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value integer(kind=int64), (minval(shape(A))-abs(k))

  • private module function diag_iint8(v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: v(:)

    Return Value integer(kind=int8), (size(v),size(v))

  • private module function diag_iint8_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value integer(kind=int8), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_iint8_mat(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)

    Return Value integer(kind=int8), (minval(shape(A)))

  • private module function diag_iint8_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value integer(kind=int8), (minval(shape(A))-abs(k))

  • private module function diag_rdp(v) result(res)

    Arguments

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

    Return Value real(kind=dp), (size(v),size(v))

  • private module function diag_rdp_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value real(kind=dp), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_rdp_mat(A) result(res)

    Arguments

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

    Return Value real(kind=dp), (minval(shape(A)))

  • private module function diag_rdp_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value real(kind=dp), (minval(shape(A))-abs(k))

  • private module function diag_rsp(v) result(res)

    Arguments

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

    Return Value real(kind=sp), (size(v),size(v))

  • private module function diag_rsp_k(v, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: v(:)
    integer, intent(in) :: k

    Return Value real(kind=sp), (size(v)+abs(k),size(v)+abs(k))

  • private module function diag_rsp_mat(A) result(res)

    Arguments

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

    Return Value real(kind=sp), (minval(shape(A)))

  • private module function diag_rsp_mat_k(A, k) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    integer, intent(in) :: k

    Return Value real(kind=sp), (minval(shape(A))-abs(k))

public interface eig

Solves the eigendecomposition for square matrix . (Specification)

Summary

Subroutine interface for computing eigenvalues and eigenvectors of a square matrix.

Description

This interface provides methods for computing the eigenvalues, and optionally eigenvectors, of a general square matrix. Supported data types include real and complex, and no assumption is made on the matrix structure. The user may request either left, right, or both eigenvectors to be returned. They are returned as columns of a square matrix with the same size as A. Preallocated space for both eigenvalues lambda and the eigenvector matrices must be user-provided.

Note

The solution is based on LAPACK's general eigenproblem solvers *GEEV.

Note

BLAS/LAPACK backends do not currently support extended precision (xdp).

  • private module subroutine stdlib_linalg_eig_c(a, lambda, right, left, overwrite_a, err)

    Eigendecomposition of matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    complex(kind=sp), intent(out) :: lambda(:)

    Array of eigenvalues

    complex(kind=sp), intent(out), optional, target :: right(:,:)

    The columns of RIGHT contain the right eigenvectors of A

    complex(kind=sp), intent(out), optional, target :: left(:,:)

    The columns of LEFT contain the left eigenvectors of A

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_eig_d(a, lambda, right, left, overwrite_a, err)

    Eigendecomposition of matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    complex(kind=dp), intent(out) :: lambda(:)

    Array of eigenvalues

    complex(kind=dp), intent(out), optional, target :: right(:,:)

    The columns of RIGHT contain the right eigenvectors of A

    complex(kind=dp), intent(out), optional, target :: left(:,:)

    The columns of LEFT contain the left eigenvectors of A

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_eig_s(a, lambda, right, left, overwrite_a, err)

    Eigendecomposition of matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    complex(kind=sp), intent(out) :: lambda(:)

    Array of eigenvalues

    complex(kind=sp), intent(out), optional, target :: right(:,:)

    The columns of RIGHT contain the right eigenvectors of A

    complex(kind=sp), intent(out), optional, target :: left(:,:)

    The columns of LEFT contain the left eigenvectors of A

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_eig_z(a, lambda, right, left, overwrite_a, err)

    Eigendecomposition of matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    complex(kind=dp), intent(out) :: lambda(:)

    Array of eigenvalues

    complex(kind=dp), intent(out), optional, target :: right(:,:)

    The columns of RIGHT contain the right eigenvectors of A

    complex(kind=dp), intent(out), optional, target :: left(:,:)

    The columns of LEFT contain the left eigenvectors of A

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_real_eig_d(a, lambda, right, left, overwrite_a, err)

    Eigendecomposition of matrix A returning an array lambda of real eigenvalues, and optionally right or left eigenvectors. Returns an error if the eigenvalues had non-trivial imaginary parts.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=dp), intent(out) :: lambda(:)

    Array of real eigenvalues

    complex(kind=dp), intent(out), optional, target :: right(:,:)

    The columns of RIGHT contain the right eigenvectors of A

    complex(kind=dp), intent(out), optional, target :: left(:,:)

    The columns of LEFT contain the left eigenvectors of A

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_real_eig_s(a, lambda, right, left, overwrite_a, err)

    Eigendecomposition of matrix A returning an array lambda of real eigenvalues, and optionally right or left eigenvectors. Returns an error if the eigenvalues had non-trivial imaginary parts.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=sp), intent(out) :: lambda(:)

    Array of real eigenvalues

    complex(kind=sp), intent(out), optional, target :: right(:,:)

    The columns of RIGHT contain the right eigenvectors of A

    complex(kind=sp), intent(out), optional, target :: left(:,:)

    The columns of LEFT contain the left eigenvectors of A

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

public interface eigh

Solves the eigendecomposition for a real symmetric or complex Hermitian square matrix. (Specification)

Summary

Subroutine interface for computing eigenvalues and eigenvectors of a real symmetric or complex Hermitian square matrix.

Description

This interface provides methods for computing the eigenvalues, and optionally eigenvectors, of a real symmetric or complex Hermitian square matrix. Supported data types include real and complex. The matrix must be symmetric (if real) or Hermitian (if complex). Only the lower or upper half of the matrix is accessed, and the user can select which using the optional upper_a flag (default: use lower half). The vectors are orthogonal, and may be returned as columns of an optional matrix vectors with the same kind and size as A. Preallocated space for both eigenvalues lambda and the eigenvector matrix must be user-provided.

Note

The solution is based on LAPACK's eigenproblem solvers *SYEV/*HEEV.

Note

BLAS/LAPACK backends do not currently support extended precision (xdp).

  • private module subroutine stdlib_linalg_eigh_c(a, lambda, vectors, upper_a, overwrite_a, err)

    Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=sp), intent(out) :: lambda(:)

    Array of eigenvalues

    complex(kind=sp), intent(out), optional, target :: vectors(:,:)

    The columns of vectors contain the orthonormal eigenvectors of A

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_eigh_d(a, lambda, vectors, upper_a, overwrite_a, err)

    Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=dp), intent(out) :: lambda(:)

    Array of eigenvalues

    real(kind=dp), intent(out), optional, target :: vectors(:,:)

    The columns of vectors contain the orthonormal eigenvectors of A

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_eigh_s(a, lambda, vectors, upper_a, overwrite_a, err)

    Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=sp), intent(out) :: lambda(:)

    Array of eigenvalues

    real(kind=sp), intent(out), optional, target :: vectors(:,:)

    The columns of vectors contain the orthonormal eigenvectors of A

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_eigh_z(a, lambda, vectors, upper_a, overwrite_a, err)

    Eigendecomposition of a real symmetric or complex Hermitian matrix A returning an array lambda of eigenvalues, and optionally right or left eigenvectors.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=dp), intent(out) :: lambda(:)

    Array of eigenvalues

    complex(kind=dp), intent(out), optional, target :: vectors(:,:)

    The columns of vectors contain the orthonormal eigenvectors of A

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

public interface eigvals

Returns the eigenvalues , , for square matrix . (Specification)

Summary

Function interface for computing the eigenvalues of a square matrix.

Description

This interface provides functions for returning the eigenvalues of a general square matrix. Supported data types include real and complex, and no assumption is made on the matrix structure. An error stop is thrown in case of failure; otherwise, error information can be returned as an optional type(linalg_state_type) output flag.

Note

The solution is based on LAPACK's general eigenproblem solvers *GEEV.

Note

BLAS/LAPACK backends do not currently support extended precision (xdp).

  • private module function stdlib_linalg_eigvals_c(a, err) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_eigvals_d(a, err) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_eigvals_noerr_c(a) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    Array of singular values

  • private module function stdlib_linalg_eigvals_noerr_d(a) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    Array of singular values

  • private module function stdlib_linalg_eigvals_noerr_s(a) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    Array of singular values

  • private module function stdlib_linalg_eigvals_noerr_z(a) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    Array of singular values

  • private module function stdlib_linalg_eigvals_s(a, err) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_eigvals_z(a, err) result(lambda)

    Return an array of eigenvalues of matrix A.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

public interface eigvalsh

Returns the eigenvalues , , for a real symmetric or complex Hermitian square matrix. (Specification)

Summary

Function interface for computing the eigenvalues of a real symmetric or complex hermitian square matrix.

Description

This interface provides functions for returning the eigenvalues of a real symmetric or complex Hermitian square matrix. Supported data types include real and complex. The matrix must be symmetric (if real) or Hermitian (if complex). Only the lower or upper half of the matrix is accessed, and the user can select which using the optional upper_a flag (default: use lower half). An error stop is thrown in case of failure; otherwise, error information can be returned as an optional type(linalg_state_type) output flag.

Note

The solution is based on LAPACK's eigenproblem solvers *SYEV/*HEEV.

Note

BLAS/LAPACK backends do not currently support extended precision (xdp).

  • private module function stdlib_linalg_eigvalsh_c(a, upper_a, err) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_eigvalsh_d(a, upper_a, err) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_eigvalsh_noerr_c(a, upper_a) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    Array of singular values

  • private module function stdlib_linalg_eigvalsh_noerr_d(a, upper_a) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    Array of singular values

  • private module function stdlib_linalg_eigvalsh_noerr_s(a, upper_a) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    Array of singular values

  • private module function stdlib_linalg_eigvalsh_noerr_z(a, upper_a) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    Array of singular values

  • private module function stdlib_linalg_eigvalsh_s(a, upper_a, err) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_eigvalsh_z(a, upper_a, err) result(lambda)

    Return an array of eigenvalues of real symmetric / complex hermitian A

    Arguments

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

    Input matrix A[m,n]

    logical(kind=lk), intent(in), optional :: upper_a

    [optional] Should the upper/lower half of A be used? Default: lower

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

public interface inv

Inverse of a square matrix (Specification)

Summary

This interface provides methods for computing the inverse of a square real or complex matrix. The inverse is defined such that .

Description

This function interface provides methods that return the inverse of a square matrix.
Supported data types include real and complex. The inverse matrix is returned as a function result. Exceptions are raised in case of singular matrix or invalid size, and trigger an error stop if the state flag err is not provided.

Note

The provided functions are intended for square matrices.

  • private module function stdlib_linalg_inverse_c(a, err) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Output matrix inverse

  • private module function stdlib_linalg_inverse_d(a, err) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Output matrix inverse

  • private module function stdlib_linalg_inverse_s(a, err) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Output matrix inverse

  • private module function stdlib_linalg_inverse_z(a, err) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Output matrix inverse

public interface invert

Inversion of a square matrix (Specification)

Summary

This interface provides methods for inverting a square real or complex matrix in-place. The inverse is defined such that .

Description

This subroutine interface provides a way to compute the inverse of a matrix.
Supported data types include real and complex. The user may provide a unique matrix argument a. In this case, a is replaced by the inverse matrix. on output. Otherwise, one may provide two separate arguments: an input matrix a and an output matrix inva. In this case, a will not be modified, and the inverse is returned in inva. Pre-allocated storage may be provided for the array of pivot indices, pivot. If all pre-allocated work spaces are provided, no internal memory allocations take place when using this interface.

Note

The provided subroutines are intended for square matrices.

  • private module subroutine stdlib_linalg_invert_inplace_c(a, pivot, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout) :: a(:,:)

    Input matrix a[n,n]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_invert_inplace_d(a, pivot, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout) :: a(:,:)

    Input matrix a[n,n]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_invert_inplace_s(a, pivot, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout) :: a(:,:)

    Input matrix a[n,n]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_invert_inplace_z(a, pivot, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout) :: a(:,:)

    Input matrix a[n,n]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_invert_split_c(a, inva, pivot, err)

    Arguments

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

    Input matrix a[n,n].

    complex(kind=sp), intent(out) :: inva(:,:)

    Inverse matrix a[n,n].

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_invert_split_d(a, inva, pivot, err)

    Arguments

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

    Input matrix a[n,n].

    real(kind=dp), intent(out) :: inva(:,:)

    Inverse matrix a[n,n].

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_invert_split_s(a, inva, pivot, err)

    Arguments

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

    Input matrix a[n,n].

    real(kind=sp), intent(out) :: inva(:,:)

    Inverse matrix a[n,n].

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_invert_split_z(a, inva, pivot, err)

    Arguments

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

    Input matrix a[n,n].

    complex(kind=dp), intent(out) :: inva(:,:)

    Inverse matrix a[n,n].

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

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

    [optional] state return flag. On error if not requested, the code will stop

public interface is_diagonal

Checks if a matrix (rank-2 array) is diagonal (Specification)

  • private pure function is_diagonal_rsp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_diagonal_rdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_diagonal_csp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_diagonal_cdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_diagonal_iint8(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_diagonal_iint16(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_diagonal_iint32(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_diagonal_iint64(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)

    Return Value logical

public interface is_hermitian

Checks if a matrix (rank-2 array) is Hermitian (Specification)

  • private pure function is_hermitian_rsp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_hermitian_rdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_hermitian_csp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_hermitian_cdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_hermitian_iint8(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_hermitian_iint16(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_hermitian_iint32(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_hermitian_iint64(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)

    Return Value logical

public interface is_hessenberg

Checks if a matrix (rank-2 array) is Hessenberg (Specification)

  • private function is_hessenberg_rsp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_hessenberg_rdp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_hessenberg_csp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_hessenberg_cdp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_hessenberg_iint8(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_hessenberg_iint16(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_hessenberg_iint32(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_hessenberg_iint64(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

public interface is_skew_symmetric

Checks if a matrix (rank-2 array) is skew-symmetric (Specification)

  • private pure function is_skew_symmetric_rsp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_skew_symmetric_rdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_skew_symmetric_csp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_skew_symmetric_cdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_skew_symmetric_iint8(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_skew_symmetric_iint16(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_skew_symmetric_iint32(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_skew_symmetric_iint64(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)

    Return Value logical

public interface is_square

Checks if a matrix (rank-2 array) is square (Specification)

  • private pure function is_square_rsp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_square_rdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_square_csp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_square_cdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_square_iint8(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_square_iint16(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_square_iint32(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_square_iint64(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)

    Return Value logical

public interface is_symmetric

Checks if a matrix (rank-2 array) is symmetric (Specification)

  • private pure function is_symmetric_rsp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_symmetric_rdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_symmetric_csp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_symmetric_cdp(A) result(res)

    Arguments

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

    Return Value logical

  • private pure function is_symmetric_iint8(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_symmetric_iint16(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_symmetric_iint32(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)

    Return Value logical

  • private pure function is_symmetric_iint64(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)

    Return Value logical

public interface is_triangular

Checks if a matrix (rank-2 array) is triangular (Specification)

  • private function is_triangular_rsp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_triangular_rdp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_triangular_csp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_triangular_cdp(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_triangular_iint8(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_triangular_iint16(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_triangular_iint32(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

  • private function is_triangular_iint64(A, uplo) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)
    character(len=1), intent(in) :: uplo

    Return Value logical

public interface kronecker_product

Computes the Kronecker product of two arrays of size M1xN1, and of M2xN2, returning an (M1M2)x(N1N2) array (Specification)

  • private pure module function kronecker_product_cdp(A, B) result(C)

    Arguments

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

    Return Value complex(kind=dp), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

  • private pure module function kronecker_product_csp(A, B) result(C)

    Arguments

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

    Return Value complex(kind=sp), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

  • private pure module function kronecker_product_iint16(A, B) result(C)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)
    integer(kind=int16), intent(in) :: B(:,:)

    Return Value integer(kind=int16), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

  • private pure module function kronecker_product_iint32(A, B) result(C)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)
    integer(kind=int32), intent(in) :: B(:,:)

    Return Value integer(kind=int32), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

  • private pure module function kronecker_product_iint64(A, B) result(C)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)
    integer(kind=int64), intent(in) :: B(:,:)

    Return Value integer(kind=int64), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

  • private pure module function kronecker_product_iint8(A, B) result(C)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)
    integer(kind=int8), intent(in) :: B(:,:)

    Return Value integer(kind=int8), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

  • private pure module function kronecker_product_rdp(A, B) result(C)

    Arguments

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

    Return Value real(kind=dp), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

  • private pure module function kronecker_product_rsp(A, B) result(C)

    Arguments

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

    Return Value real(kind=sp), (size(A,dim=1)*size(B,dim=1),size(A,dim=2)*size(B,dim=2))

public interface lstsq

Computes the squares solution to system . (Specification)

Summary

Interface for computing least squares, i.e. the 2-norm minimizing solution.

Description

This interface provides methods for computing the least squares of a linear matrix system. Supported data types include real and complex.

Note

The solution is based on LAPACK's singular value decomposition *GELSD methods.

  • private module function stdlib_linalg_c_lstsq_many(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_c_lstsq_one(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_d_lstsq_many(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_d_lstsq_one(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_s_lstsq_many(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_s_lstsq_one(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_z_lstsq_many(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_z_lstsq_one(a, b, cond, overwrite_a, rank, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

public interface lstsq_space

Computes the integer, real [, complex] working space required by the least-squares solver (Specification)

Description

This interface provides sizes of integer, real [, complex] working spaces required by the least-squares solver. These sizes can be used to pre-allocated working arrays in case several repeated least-squares solutions to a same system are sought. If pre-allocated working arrays are provided, no internal allocations will take place.

  • private pure module subroutine stdlib_linalg_c_lstsq_space_many(a, b, lrwork, liwork, lcwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: lcwork

    Size of the working space arrays

  • private pure module subroutine stdlib_linalg_c_lstsq_space_one(a, b, lrwork, liwork, lcwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: lcwork

    Size of the working space arrays

  • private pure module subroutine stdlib_linalg_d_lstsq_space_many(a, b, lrwork, liwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

  • private pure module subroutine stdlib_linalg_d_lstsq_space_one(a, b, lrwork, liwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

  • private pure module subroutine stdlib_linalg_s_lstsq_space_many(a, b, lrwork, liwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

  • private pure module subroutine stdlib_linalg_s_lstsq_space_one(a, b, lrwork, liwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

  • private pure module subroutine stdlib_linalg_z_lstsq_space_many(a, b, lrwork, liwork, lcwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: lcwork

    Size of the working space arrays

  • private pure module subroutine stdlib_linalg_z_lstsq_space_one(a, b, lrwork, liwork, lcwork)

    Arguments

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

    Input matrix a[m,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    integer(kind=ilp), intent(out) :: lrwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: liwork

    Size of the working space arrays

    integer(kind=ilp), intent(out) :: lcwork

    Size of the working space arrays

public interface operator(.det.)

Determinant operator of a square matrix (Specification)

Summary

Pure operator interface for computing matrix determinant.

Description

This pure operator interface provides a convenient way to compute the determinant of a matrix. Supported data types include real and complex.

Note

The provided functions are intended for square matrices.

Note

BLAS/LAPACK backends do not currently support extended precision (xdp).

Example

    ! ...
    real(sp) :: matrix(3,3), d
    matrix = reshape([1, 2, 3, 4, 5, 6, 7, 8, 9], [3, 3])
    d = .det.matrix
    ! ...
  • private interface stdlib_linalg_pure_rspdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_pure_rdpdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_pure_cspdeterminant()

    Arguments

    None
  • private interface stdlib_linalg_pure_cdpdeterminant()

    Arguments

    None

public interface operator(.inv.)

Inverse operator of a square matrix (Specification)

Summary

Operator interface for computing the inverse of a square real or complex matrix.

Description

This operator interface provides a convenient way to compute the inverse of a matrix. Supported data types include real and complex. On input errors or singular matrix, NaNs will be returned.

Note

The provided functions are intended for square matrices.

  • private module function stdlib_linalg_inverse_c_operator(a) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    Result matrix

  • private module function stdlib_linalg_inverse_d_operator(a) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    Result matrix

  • private module function stdlib_linalg_inverse_s_operator(a) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    Result matrix

  • private module function stdlib_linalg_inverse_z_operator(a) result(inva)

    Arguments

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

    Input matrix a[n,n]

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

    Result matrix

public interface outer_product

Computes the outer product of two vectors, returning a rank-2 array (Specification)

  • private pure module function outer_product_cdp(u, v) result(res)

    Arguments

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

    Return Value complex(kind=dp), (size(u),size(v))

  • private pure module function outer_product_csp(u, v) result(res)

    Arguments

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

    Return Value complex(kind=sp), (size(u),size(v))

  • private pure module function outer_product_iint16(u, v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: u(:)
    integer(kind=int16), intent(in) :: v(:)

    Return Value integer(kind=int16), (size(u),size(v))

  • private pure module function outer_product_iint32(u, v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: u(:)
    integer(kind=int32), intent(in) :: v(:)

    Return Value integer(kind=int32), (size(u),size(v))

  • private pure module function outer_product_iint64(u, v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: u(:)
    integer(kind=int64), intent(in) :: v(:)

    Return Value integer(kind=int64), (size(u),size(v))

  • private pure module function outer_product_iint8(u, v) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: u(:)
    integer(kind=int8), intent(in) :: v(:)

    Return Value integer(kind=int8), (size(u),size(v))

  • private pure module function outer_product_rdp(u, v) result(res)

    Arguments

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

    Return Value real(kind=dp), (size(u),size(v))

  • private pure module function outer_product_rsp(u, v) result(res)

    Arguments

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

    Return Value real(kind=sp), (size(u),size(v))

public interface solve

Solves the linear system for the unknown vector from a square matrix . (Specification)

Summary

Interface for solving a linear system arising from a general matrix.

Description

This interface provides methods for computing the solution of a linear matrix system. Supported data types include real and complex. No assumption is made on the matrix structure. The function can solve simultaneously either one (from a 1-d right-hand-side vector b(:)) or several (from a 2-d right-hand-side vector b(:,:)) systems.

Note

The solution is based on LAPACK's generic LU decomposition based solvers *GESV.

  • private pure module function stdlib_linalg_c_pure_solve_many(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private pure module function stdlib_linalg_c_pure_solve_one(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_c_solve_many(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_c_solve_one(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private pure module function stdlib_linalg_d_pure_solve_many(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private pure module function stdlib_linalg_d_pure_solve_one(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_d_solve_many(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_d_solve_one(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private pure module function stdlib_linalg_s_pure_solve_many(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private pure module function stdlib_linalg_s_pure_solve_one(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_s_solve_many(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_s_solve_one(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private pure module function stdlib_linalg_z_pure_solve_many(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private pure module function stdlib_linalg_z_pure_solve_one(a, b) result(x)

    Arguments

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

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_z_solve_many(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

  • private module function stdlib_linalg_z_solve_one(a, b, overwrite_a, err) result(x)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Result array/matrix x[n] or x[n,nrhs]

public interface solve_lstsq

Computes the squares solution to system . (Specification)

Summary

Subroutine interface for computing least squares, i.e. the 2-norm minimizing solution.

Description

This interface provides methods for computing the least squares of a linear matrix system using a subroutine. Supported data types include real and complex. If pre-allocated work spaces are provided, no internal memory allocations take place when using this interface.

Note

The solution is based on LAPACK's singular value decomposition *GELSD methods.

  • private module subroutine stdlib_linalg_c_solve_lstsq_many(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=sp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=sp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    complex(kind=sp), intent(inout), optional, target :: cmpl_storage(:)

    [optional] complex working storage space

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=sp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_c_solve_lstsq_one(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=sp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=sp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    complex(kind=sp), intent(inout), optional, target :: cmpl_storage(:)

    [optional] complex working storage space

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=sp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_d_solve_lstsq_many(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=dp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=dp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_d_solve_lstsq_one(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=dp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=dp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_s_solve_lstsq_many(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=sp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=sp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_s_solve_lstsq_one(a, b, x, real_storage, int_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=sp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    real(kind=sp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=sp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_z_solve_lstsq_many(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=dp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=dp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    complex(kind=dp), intent(inout), optional, target :: cmpl_storage(:)

    [optional] complex working storage space

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=dp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_z_solve_lstsq_one(a, b, x, real_storage, int_storage, cmpl_storage, cond, singvals, overwrite_a, rank, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=dp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    real(kind=dp), intent(inout), optional, target :: real_storage(:)

    [optional] real working storage space

    integer(kind=ilp), intent(inout), optional, target :: int_storage(:)

    [optional] integer working storage space

    complex(kind=dp), intent(inout), optional, target :: cmpl_storage(:)

    [optional] complex working storage space

    real(kind=dp), intent(in), optional :: cond

    [optional] cutoff for rank evaluation: singular values s(i)<=cond*maxval(s) are considered 0.

    real(kind=dp), intent(out), optional, target :: singvals(:)

    [optional] list of singular values [min(m,n)], in descending magnitude order, returned by the SVD

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A,b data be overwritten and destroyed?

    integer(kind=ilp), intent(out), optional :: rank

    [optional] Return rank of A

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

    [optional] state return flag. On error if not requested, the code will stop

public interface solve_lu

Solves the linear system for the unknown vector from a square matrix . (Specification)

Summary

Subroutine interface for solving a linear system using LU decomposition.

Description

This interface provides methods for computing the solution of a linear matrix system using a subroutine. Supported data types include real and complex. No assumption is made on the matrix structure. Preallocated space for the solution vector x is user-provided, and it may be provided for the array of pivot indices, pivot. If all pre-allocated work spaces are provided, no internal memory allocations take place when using this interface.
The function can solve simultaneously either one (from a 1-d right-hand-side vector b(:)) or several (from a 2-d right-hand-side vector b(:,:)) systems.

Note

The solution is based on LAPACK's generic LU decomposition based solvers *GESV.

  • private pure module subroutine stdlib_linalg_c_solve_lu_many(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=sp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private pure module subroutine stdlib_linalg_c_solve_lu_one(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=sp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private pure module subroutine stdlib_linalg_d_solve_lu_many(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private pure module subroutine stdlib_linalg_d_solve_lu_one(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=dp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private pure module subroutine stdlib_linalg_s_solve_lu_many(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private pure module subroutine stdlib_linalg_s_solve_lu_one(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    real(kind=sp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private pure module subroutine stdlib_linalg_z_solve_lu_many(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=dp), intent(inout), contiguous, target :: x(:,:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

  • private pure module subroutine stdlib_linalg_z_solve_lu_one(a, b, x, pivot, overwrite_a, err)

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix a[n,n]

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

    Right hand side vector or array, b[n] or b[n,nrhs]

    complex(kind=dp), intent(inout), contiguous, target :: x(:)

    Result array/matrix x[n] or x[n,nrhs]

    integer(kind=ilp), intent(inout), optional, target :: pivot(:)

    [optional] Storage array for the diagonal pivot indices

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

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

    [optional] state return flag. On error if not requested, the code will stop

public interface svd

Computes the singular value decomposition of a real or complex 2d matrix. (Specification)

Summary

Interface for computing the singular value decomposition of a real or complex 2d matrix.

Description

This interface provides methods for computing the singular value decomposition of a matrix. Supported data types include real and complex. The subroutine returns a real array of singular values, and optionally, left- and right- singular vector matrices, U and V. For a matrix A with size [m,n], full matrix storage for U and V should be [m,m] and [n,n]. It is possible to use partial storage [m,k] and [k,n], k=min(m,n), choosing full_matrices=.false..

Note

The solution is based on LAPACK's singular value decomposition *GESDD methods.

Example

    real(sp) :: a(2,3), s(2), u(2,2), vt(3,3) 
    a = reshape([3,2, 2,3, 2,-2],[2,3])

    call svd(A,s,u,v)
    print *, 'singular values = ',s
  • private module subroutine stdlib_linalg_svd_c(a, s, u, vt, overwrite_a, full_matrices, err)

    Summary

    Compute singular value decomposition of a matrix

    Description

    This function computes the singular value decomposition of a real or complex matrix , and returns the array of singular values, and optionally the left matrix containing the left unitary singular vectors, and the right matrix , containing the right unitary singular vectors.

    param: a Input matrix of size [m,n]. param: s Output real array of size [min(m,n)] returning a list of singular values. param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns. param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
    param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten. param: full_matrices [optional] If .true. (default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n). param: err [optional] State return flag.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=sp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=sp), intent(out) :: s(:)

    Array of singular values

    complex(kind=sp), intent(out), optional, target :: u(:,:)

    The columns of U contain the left singular vectors

    complex(kind=sp), intent(out), optional, target :: vt(:,:)

    The rows of V^T contain the right singular vectors

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

    logical(kind=lk), intent(in), optional :: full_matrices

    [optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n)

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_svd_d(a, s, u, vt, overwrite_a, full_matrices, err)

    Summary

    Compute singular value decomposition of a matrix

    Description

    This function computes the singular value decomposition of a real or complex matrix , and returns the array of singular values, and optionally the left matrix containing the left unitary singular vectors, and the right matrix , containing the right unitary singular vectors.

    param: a Input matrix of size [m,n]. param: s Output real array of size [min(m,n)] returning a list of singular values. param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns. param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
    param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten. param: full_matrices [optional] If .true. (default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n). param: err [optional] State return flag.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=dp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=dp), intent(out) :: s(:)

    Array of singular values

    real(kind=dp), intent(out), optional, target :: u(:,:)

    The columns of U contain the left singular vectors

    real(kind=dp), intent(out), optional, target :: vt(:,:)

    The rows of V^T contain the right singular vectors

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

    logical(kind=lk), intent(in), optional :: full_matrices

    [optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n)

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_svd_s(a, s, u, vt, overwrite_a, full_matrices, err)

    Summary

    Compute singular value decomposition of a matrix

    Description

    This function computes the singular value decomposition of a real or complex matrix , and returns the array of singular values, and optionally the left matrix containing the left unitary singular vectors, and the right matrix , containing the right unitary singular vectors.

    param: a Input matrix of size [m,n]. param: s Output real array of size [min(m,n)] returning a list of singular values. param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns. param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
    param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten. param: full_matrices [optional] If .true. (default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n). param: err [optional] State return flag.

    Arguments

    Type IntentOptional Attributes Name
    real(kind=sp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=sp), intent(out) :: s(:)

    Array of singular values

    real(kind=sp), intent(out), optional, target :: u(:,:)

    The columns of U contain the left singular vectors

    real(kind=sp), intent(out), optional, target :: vt(:,:)

    The rows of V^T contain the right singular vectors

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

    logical(kind=lk), intent(in), optional :: full_matrices

    [optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n)

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

    [optional] state return flag. On error if not requested, the code will stop

  • private module subroutine stdlib_linalg_svd_z(a, s, u, vt, overwrite_a, full_matrices, err)

    Summary

    Compute singular value decomposition of a matrix

    Description

    This function computes the singular value decomposition of a real or complex matrix , and returns the array of singular values, and optionally the left matrix containing the left unitary singular vectors, and the right matrix , containing the right unitary singular vectors.

    param: a Input matrix of size [m,n]. param: s Output real array of size [min(m,n)] returning a list of singular values. param: u [optional] Output left singular matrix of size [m,m] or [m,min(m,n)] (.not.full_matrices). Contains singular vectors as columns. param: vt [optional] Output right singular matrix of size [n,n] or [min(m,n),n] (.not.full_matrices). Contains singular vectors as rows.
    param: overwrite_a [optional] Flag indicating if the input matrix can be overwritten. param: full_matrices [optional] If .true. (default), matrices and have size [m,m], [n,n]. Otherwise, they are [m,k], [k,n] with k=min(m,n). param: err [optional] State return flag.

    Arguments

    Type IntentOptional Attributes Name
    complex(kind=dp), intent(inout), target :: a(:,:)

    Input matrix A[m,n]

    real(kind=dp), intent(out) :: s(:)

    Array of singular values

    complex(kind=dp), intent(out), optional, target :: u(:,:)

    The columns of U contain the left singular vectors

    complex(kind=dp), intent(out), optional, target :: vt(:,:)

    The rows of V^T contain the right singular vectors

    logical(kind=lk), intent(in), optional :: overwrite_a

    [optional] Can A data be overwritten and destroyed?

    logical(kind=lk), intent(in), optional :: full_matrices

    [optional] full matrices have shape(u)==[m,m], shape(vh)==[n,n] (default); otherwise they are shape(u)==[m,k] and shape(vh)==[k,n] with k=min(m,n)

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

    [optional] state return flag. On error if not requested, the code will stop

public interface svdvals

Computes the singular values of a real or complex 2d matrix. (Specification)

Summary

Function interface for computing the array of singular values from the singular value decomposition of a real or complex 2d matrix.

Description

This interface provides methods for computing the singular values a 2d matrix. Supported data types include real and complex. The function returns a real array of singular values, with size [min(m,n)].

Note

The solution is based on LAPACK's singular value decomposition *GESDD methods.

Example

    real(sp) :: a(2,3), s(2)
    a = reshape([3,2, 2,3, 2,-2],[2,3])

    s = svdvals(A)
    print *, 'singular values = ',s
  • private module function stdlib_linalg_svdvals_c(a, err) result(s)

    Summary

    Compute singular values from the singular-value decomposition of a matrix .

    Description

    This function returns the array of singular values from the singular value decomposition of a real or complex matrix .

    param: a Input matrix of size [m,n]. param: err [optional] State return flag.

    Return value

    param: s real array of size [min(m,n)] returning a list of singular values.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_svdvals_d(a, err) result(s)

    Summary

    Compute singular values from the singular-value decomposition of a matrix .

    Description

    This function returns the array of singular values from the singular value decomposition of a real or complex matrix .

    param: a Input matrix of size [m,n]. param: err [optional] State return flag.

    Return value

    param: s real array of size [min(m,n)] returning a list of singular values.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_svdvals_s(a, err) result(s)

    Summary

    Compute singular values from the singular-value decomposition of a matrix .

    Description

    This function returns the array of singular values from the singular value decomposition of a real or complex matrix .

    param: a Input matrix of size [m,n]. param: err [optional] State return flag.

    Return value

    param: s real array of size [min(m,n)] returning a list of singular values.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

  • private module function stdlib_linalg_svdvals_z(a, err) result(s)

    Summary

    Compute singular values from the singular-value decomposition of a matrix .

    Description

    This function returns the array of singular values from the singular value decomposition of a real or complex matrix .

    param: a Input matrix of size [m,n]. param: err [optional] State return flag.

    Return value

    param: s real array of size [min(m,n)] returning a list of singular values.

    Arguments

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

    Input matrix A[m,n]

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

    [optional] state return flag. On error if not requested, the code will stop

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

    Array of singular values

public interface trace

Computes the trace of a matrix (Specification)

  • private function trace_rsp(A) result(res)

    Arguments

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

    Return Value real(kind=sp)

  • private function trace_rdp(A) result(res)

    Arguments

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

    Return Value real(kind=dp)

  • private function trace_csp(A) result(res)

    Arguments

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

    Return Value complex(kind=sp)

  • private function trace_cdp(A) result(res)

    Arguments

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

    Return Value complex(kind=dp)

  • private function trace_iint8(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int8), intent(in) :: A(:,:)

    Return Value integer(kind=int8)

  • private function trace_iint16(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int16), intent(in) :: A(:,:)

    Return Value integer(kind=int16)

  • private function trace_iint32(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int32), intent(in) :: A(:,:)

    Return Value integer(kind=int32)

  • private function trace_iint64(A) result(res)

    Arguments

    Type IntentOptional Attributes Name
    integer(kind=int64), intent(in) :: A(:,:)

    Return Value integer(kind=int64)


Functions

public pure function eye(dim1, dim2) result(result)

License
Creative Commons License
Version
experimental

Constructs the identity matrix. (Specification)

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: dim1
integer, intent(in), optional :: dim2

Return Value integer(kind=int8), allocatable, (:,:)