Contents


NAME

     cgeev - compute for an N-by-N complex nonsymmetric matrix A,
     the  eigenvalues  and,  optionally,  the  left  and/or right
     eigenvectors

SYNOPSIS

     SUBROUTINE CGEEV(JOBVL, JOBVR, N, A, LDA, W, VL, LDVL, VR, LDVR,
           WORK, LDWORK, WORK2, INFO)

     CHARACTER * 1 JOBVL, JOBVR
     COMPLEX A(LDA,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
     INTEGER N, LDA, LDVL, LDVR, LDWORK, INFO
     REAL WORK2(*)

     SUBROUTINE CGEEV_64(JOBVL, JOBVR, N, A, LDA, W, VL, LDVL, VR, LDVR,
           WORK, LDWORK, WORK2, INFO)

     CHARACTER * 1 JOBVL, JOBVR
     COMPLEX A(LDA,*), W(*), VL(LDVL,*), VR(LDVR,*), WORK(*)
     INTEGER*8 N, LDA, LDVL, LDVR, LDWORK, INFO
     REAL WORK2(*)

  F95 INTERFACE
     SUBROUTINE GEEV(JOBVL, JOBVR, [N], A, [LDA], W, VL, [LDVL], VR, [LDVR],
            [WORK], [LDWORK], [WORK2], [INFO])

     CHARACTER(LEN=1) :: JOBVL, JOBVR
     COMPLEX, DIMENSION(:) :: W, WORK
     COMPLEX, DIMENSION(:,:) :: A, VL, VR
     INTEGER :: N, LDA, LDVL, LDVR, LDWORK, INFO
     REAL, DIMENSION(:) :: WORK2

     SUBROUTINE GEEV_64(JOBVL, JOBVR, [N], A, [LDA], W, VL, [LDVL], VR,
            [LDVR], [WORK], [LDWORK], [WORK2], [INFO])

     CHARACTER(LEN=1) :: JOBVL, JOBVR
     COMPLEX, DIMENSION(:) :: W, WORK
     COMPLEX, DIMENSION(:,:) :: A, VL, VR
     INTEGER(8) :: N, LDA, LDVL, LDVR, LDWORK, INFO
     REAL, DIMENSION(:) :: WORK2

  C INTERFACE
     #include <sunperf.h>

     void cgeev(char jobvl, char jobvr, int n,  complex  *a,  int
               lda,  complex  *w,  complex *vl, int ldvl, complex
               *vr, int ldvr, int *info);
     void cgeev_64(char jobvl, char jobvr, long  n,  complex  *a,
               long lda, complex *w, complex *vl, long ldvl, com-
               plex *vr, long ldvr, long *info);

PURPOSE

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

ARGUMENTS

     JOBVL (input)
               = 'N': left eigenvectors of A are not computed;
               = 'V': left eigenvectors of are computed.

     JOBVR (input)
               = 'N': right eigenvectors of A are not computed;
               = 'V': right eigenvectors of A are computed.

     N (input) The order of the matrix A. N >= 0.

     A (input/output)
               On entry, the N-by-N matrix A.   On  exit,  A  has
               been overwritten.

     LDA (input)
               The leading dimension of  the  array  A.   LDA  >=
               max(1,N).

     W (output)
               W contains the computed eigenvalues.

     VL (input)
               If JOBVL = 'V', the  left  eigenvectors  u(j)  are
               stored  one after another in the columns of VL, in
               the same order as their eigenvalues.  If  JOBVL  =
               'N',  VL  is  not referenced.  u(j) = VL(:,j), the
               j-th column of VL.

     LDVL (input)
               The leading dimension of the array VL.  LDVL >= 1;
               if JOBVL = 'V', LDVL >= N.

     VR (input)
               If JOBVR = 'V', the right  eigenvectors  v(j)  are
               stored  one after another in the columns of VR, in
               the same order as their eigenvalues.  If  JOBVR  =
               'N',  VR  is  not referenced.  v(j) = VR(:,j), the
               j-th column of VR.

     LDVR (input)
               The leading dimension of the array VR.  LDVR >= 1;
               if JOBVR = 'V', LDVR >= N.

     WORK (workspace)
               On exit, if INFO = 0, WORK(1) returns the  optimal
               LDWORK.

     LDWORK (input)
               The  dimension  of  the  array  WORK.   LDWORK  >=
               max(1,2*N).   For  good  performance,  LDWORK must
               generally be larger.

               If LDWORK = -1, then a workspace query is assumed;
               the  routine  only  calculates the optimal size of
               the WORK array, returns this value  as  the  first
               entry  of  the  WORK  array,  and no error message
               related to LDWORK is issued by XERBLA.

     WORK2 (workspace)
               dimension(2*N)

     INFO (output)
               = 0:  successful exit
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.
               > 0:  if INFO = i, the QR algorithm failed to com-
               pute all the eigenvalues, and no eigenvectors have
               been computed; elements and  i+1:N  of  W  contain
               eigenvalues which have converged.