geev Interface

public interface geev

GEEV computes for an N-by-N complex nonsymmetric matrix A, the eigenvalues and, optionally, the left and/or right eigenvectors. The right eigenvector v(j) of A satisfies A * v(j) = lambda(j) * v(j) where lambda(j) is its eigenvalue. The left eigenvector u(j) of A satisfies u(j)H * A = lambda(j) * u(j)H where u(j)**H denotes the conjugate transpose of u(j). The computed eigenvectors are normalized to have Euclidean norm equal to 1 and largest component real.


Subroutines

public subroutine cgeev(jobvl, jobvr, n, a, lda, w, vl, ldvl, vr, ldvr, work, lwork, rwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvl
character(len=1), intent(in) :: jobvr
integer(kind=ilp), intent(in) :: n
complex(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=sp), intent(out) :: w(*)
complex(kind=sp), intent(out) :: vl(ldvl,*)
integer(kind=ilp), intent(in) :: ldvl
complex(kind=sp), intent(out) :: vr(ldvr,*)
integer(kind=ilp), intent(in) :: ldvr
complex(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
real(kind=sp), intent(out) :: rwork(*)
integer(kind=ilp), intent(out) :: info

public subroutine dgeev(jobvl, jobvr, n, a, lda, wr, wi, vl, ldvl, vr, ldvr, work, lwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvl
character(len=1), intent(in) :: jobvr
integer(kind=ilp), intent(in) :: n
real(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=dp), intent(out) :: wr(*)
real(kind=dp), intent(out) :: wi(*)
real(kind=dp), intent(out) :: vl(ldvl,*)
integer(kind=ilp), intent(in) :: ldvl
real(kind=dp), intent(out) :: vr(ldvr,*)
integer(kind=ilp), intent(in) :: ldvr
real(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: info

public subroutine sgeev(jobvl, jobvr, n, a, lda, wr, wi, vl, ldvl, vr, ldvr, work, lwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvl
character(len=1), intent(in) :: jobvr
integer(kind=ilp), intent(in) :: n
real(kind=sp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=sp), intent(out) :: wr(*)
real(kind=sp), intent(out) :: wi(*)
real(kind=sp), intent(out) :: vl(ldvl,*)
integer(kind=ilp), intent(in) :: ldvl
real(kind=sp), intent(out) :: vr(ldvr,*)
integer(kind=ilp), intent(in) :: ldvr
real(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: info

public subroutine zgeev(jobvl, jobvr, n, a, lda, w, vl, ldvl, vr, ldvr, work, lwork, rwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: jobvl
character(len=1), intent(in) :: jobvr
integer(kind=ilp), intent(in) :: n
complex(kind=dp), intent(inout) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=dp), intent(out) :: w(*)
complex(kind=dp), intent(out) :: vl(ldvl,*)
integer(kind=ilp), intent(in) :: ldvl
complex(kind=dp), intent(out) :: vr(ldvr,*)
integer(kind=ilp), intent(in) :: ldvr
complex(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
real(kind=dp), intent(out) :: rwork(*)
integer(kind=ilp), intent(out) :: info

Module Procedures

public interface stdlib_cgeev()

Arguments

None

public interface stdlib_dgeev()

Arguments

None

public interface stdlib_sgeev()

Arguments

None

public interface stdlib_zgeev()

Arguments

None