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 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.

Note

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

  • 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 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.

Note

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

  • 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.

Note

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

  • 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.

Note

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

  • 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 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, (:,:)