gees Interface

public interface gees

GEES computes for an N-by-N complex nonsymmetric matrix A, the eigenvalues, the Schur form T, and, optionally, the matrix of Schur vectors Z. This gives the Schur factorization A = ZT(Z**H). Optionally, it also orders the eigenvalues on the diagonal of the Schur form so that selected eigenvalues are at the top left. The leading columns of Z then form an orthonormal basis for the invariant subspace corresponding to the selected eigenvalues. A complex matrix is in Schur form if it is upper triangular.


Subroutines

public subroutine cgees(jobvs, sort, select, n, a, lda, sdim, w, vs, ldvs, work, lwork, rwork, bwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvs
character(len=1), intent(in) :: sort
procedure(stdlib_select_c) :: select
integer(kind=ilp), intent(in) :: n
complex(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
integer(kind=ilp), intent(out) :: sdim
complex(kind=sp), intent(out) :: w(*)
complex(kind=sp), intent(out) :: vs(ldvs,*)
integer(kind=ilp), intent(in) :: ldvs
complex(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
real(kind=sp), intent(out) :: rwork(*)
logical(kind=lk), intent(out) :: bwork(*)
integer(kind=ilp), intent(out) :: info

public subroutine dgees(jobvs, sort, select, n, a, lda, sdim, wr, wi, vs, ldvs, work, lwork, bwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvs
character(len=1), intent(in) :: sort
procedure(stdlib_select_d) :: select
integer(kind=ilp), intent(in) :: n
real(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
integer(kind=ilp), intent(out) :: sdim
real(kind=dp), intent(out) :: wr(*)
real(kind=dp), intent(out) :: wi(*)
real(kind=dp), intent(out) :: vs(ldvs,*)
integer(kind=ilp), intent(in) :: ldvs
real(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
logical(kind=lk), intent(out) :: bwork(*)
integer(kind=ilp), intent(out) :: info

public subroutine sgees(jobvs, sort, select, n, a, lda, sdim, wr, wi, vs, ldvs, work, lwork, bwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvs
character(len=1), intent(in) :: sort
procedure(stdlib_select_s) :: select
integer(kind=ilp), intent(in) :: n
real(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
integer(kind=ilp), intent(out) :: sdim
real(kind=sp), intent(out) :: wr(*)
real(kind=sp), intent(out) :: wi(*)
real(kind=sp), intent(out) :: vs(ldvs,*)
integer(kind=ilp), intent(in) :: ldvs
real(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
logical(kind=lk), intent(out) :: bwork(*)
integer(kind=ilp), intent(out) :: info

public subroutine zgees(jobvs, sort, select, n, a, lda, sdim, w, vs, ldvs, work, lwork, rwork, bwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvs
character(len=1), intent(in) :: sort
procedure(stdlib_select_z) :: select
integer(kind=ilp), intent(in) :: n
complex(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
integer(kind=ilp), intent(out) :: sdim
complex(kind=dp), intent(out) :: w(*)
complex(kind=dp), intent(out) :: vs(ldvs,*)
integer(kind=ilp), intent(in) :: ldvs
complex(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
real(kind=dp), intent(out) :: rwork(*)
logical(kind=lk), intent(out) :: bwork(*)
integer(kind=ilp), intent(out) :: info

Module Procedures

public interface stdlib_cgees()

Arguments

None

public interface stdlib_dgees()

Arguments

None

public interface stdlib_sgees()

Arguments

None

public interface stdlib_zgees()

Arguments

None