schur Interface

public interface schur

Computes the Schur decomposition of matrix . (Specification)

Summary

Compute the Schur decomposition of a real or complex matrix: , where is orthonormal/unitary and is upper-triangular or quasi-upper-triangular. Matrix has size [m,m].

Description

This interface provides methods for computing the Schur decomposition of a matrix. Supported data types include real and complex. If a pre-allocated workspace is provided, no internal memory allocations take place when using this interface.

The output matrix is upper-triangular for complex input matrices and quasi-upper-triangular for real input matrices (with possible blocks on the diagonal).

Note

The solution is based on LAPACK's Schur decomposition routines (*GEES).


Subroutines

private module subroutine stdlib_linalg_c_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

complex(kind=sp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

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

[optional] Output eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

complex(kind=sp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

real(kind=dp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

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

[optional] Output eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

real(kind=dp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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_c_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

complex(kind=sp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

real(kind=sp), intent(out), contiguous, target :: eigvals(:)

Output real eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

complex(kind=sp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

real(kind=dp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

real(kind=dp), intent(out), contiguous, target :: eigvals(:)

Output real eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

real(kind=dp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

real(kind=sp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

real(kind=sp), intent(out), contiguous, target :: eigvals(:)

Output real eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

real(kind=sp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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_z_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

complex(kind=dp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

real(kind=dp), intent(out), contiguous, target :: eigvals(:)

Output real eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

complex(kind=dp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

real(kind=sp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

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

[optional] Output eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

real(kind=sp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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_schur(a, t, z, eigvals, overwrite_a, storage, err)

Arguments

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

Input matrix a[m,m]

complex(kind=dp), intent(out), contiguous, target :: t(:,:)

Schur form of A: upper-triangular or quasi-upper-triangular matrix T

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

Unitary/orthonormal transformation matrix Z

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

[optional] Output eigenvalues that appear on the diagonal of T

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

[optional] Can A data be overwritten and destroyed?

complex(kind=dp), intent(inout), optional, target :: storage(:)

[optional] Provide pre-allocated workspace, size to be checked with schur_space

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

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