cgeev.f 6.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187
  1. *DECK CGEEV
  2. SUBROUTINE CGEEV (A, LDA, N, E, V, LDV, WORK, JOB, INFO)
  3. C***BEGIN PROLOGUE CGEEV
  4. C***PURPOSE Compute the eigenvalues and, optionally, the eigenvectors
  5. C of a complex general matrix.
  6. C***LIBRARY SLATEC
  7. C***CATEGORY D4A4
  8. C***TYPE COMPLEX (SGEEV-S, CGEEV-C)
  9. C***KEYWORDS EIGENVALUES, EIGENVECTORS, GENERAL MATRIX
  10. C***AUTHOR Kahaner, D. K., (NBS)
  11. C Moler, C. B., (U. of New Mexico)
  12. C Stewart, G. W., (U. of Maryland)
  13. C***DESCRIPTION
  14. C
  15. C Abstract
  16. C CGEEV computes the eigenvalues and, optionally,
  17. C the eigenvectors of a general complex matrix.
  18. C
  19. C Call Sequence Parameters-
  20. C (The values of parameters marked with * (star) will be changed
  21. C by CGEEV.)
  22. C
  23. C A* COMPLEX(LDA,N)
  24. C complex nonsymmetric input matrix.
  25. C
  26. C LDA INTEGER
  27. C set by the user to
  28. C the leading dimension of the complex array A.
  29. C
  30. C N INTEGER
  31. C set by the user to
  32. C the order of the matrices A and V, and
  33. C the number of elements in E.
  34. C
  35. C E* COMPLEX(N)
  36. C on return from CGEEV E contains the eigenvalues of A.
  37. C See also INFO below.
  38. C
  39. C V* COMPLEX(LDV,N)
  40. C on return from CGEEV if the user has set JOB
  41. C = 0 V is not referenced.
  42. C = nonzero the N eigenvectors of A are stored in the
  43. C first N columns of V. See also INFO below.
  44. C (If the input matrix A is nearly degenerate, V
  45. C will be badly conditioned, i.e. have nearly
  46. C dependent columns.)
  47. C
  48. C LDV INTEGER
  49. C set by the user to
  50. C the leading dimension of the array V if JOB is also
  51. C set nonzero. In that case N must be .LE. LDV.
  52. C If JOB is set to zero LDV is not referenced.
  53. C
  54. C WORK* REAL(3N)
  55. C temporary storage vector. Contents changed by CGEEV.
  56. C
  57. C JOB INTEGER
  58. C set by the user to
  59. C = 0 eigenvalues only to be calculated by CGEEV.
  60. C neither V nor LDV are referenced.
  61. C = nonzero eigenvalues and vectors to be calculated.
  62. C In this case A & V must be distinct arrays.
  63. C Also, if LDA > LDV, CGEEV changes all the
  64. C elements of A thru column N. If LDA < LDV,
  65. C CGEEV changes all the elements of V through
  66. C column N. If LDA = LDV only A(I,J) and V(I,
  67. C J) for I,J = 1,...,N are changed by CGEEV.
  68. C
  69. C INFO* INTEGER
  70. C on return from CGEEV the value of INFO is
  71. C = 0 normal return, calculation successful.
  72. C = K if the eigenvalue iteration fails to converge,
  73. C eigenvalues K+1 through N are correct, but
  74. C no eigenvectors were computed even if they were
  75. C requested (JOB nonzero).
  76. C
  77. C Error Messages
  78. C No. 1 recoverable N is greater than LDA
  79. C No. 2 recoverable N is less than one.
  80. C No. 3 recoverable JOB is nonzero and N is greater than LDV
  81. C No. 4 warning LDA > LDV, elements of A other than the
  82. C N by N input elements have been changed
  83. C No. 5 warning LDA < LDV, elements of V other than the
  84. C N by N output elements have been changed
  85. C
  86. C***REFERENCES (NONE)
  87. C***ROUTINES CALLED CBABK2, CBAL, COMQR, COMQR2, CORTH, SCOPY, XERMSG
  88. C***REVISION HISTORY (YYMMDD)
  89. C 800808 DATE WRITTEN
  90. C 890531 Changed all specific intrinsics to generic. (WRB)
  91. C 890531 REVISION DATE from Version 3.2
  92. C 891214 Prologue converted to Version 4.0 format. (BAB)
  93. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  94. C 900326 Removed duplicate information from DESCRIPTION section.
  95. C (WRB)
  96. C***END PROLOGUE CGEEV
  97. INTEGER I,IHI,ILO,INFO,J,K,L,LDA,LDV,MDIM,N
  98. REAL A(*),E(*),WORK(*),V(*)
  99. C***FIRST EXECUTABLE STATEMENT CGEEV
  100. IF (N .GT. LDA) CALL XERMSG ('SLATEC', 'CGEEV', 'N .GT. LDA.', 1,
  101. + 1)
  102. IF(N .GT. LDA) RETURN
  103. IF (N .LT. 1) CALL XERMSG ('SLATEC', 'CGEEV', 'N .LT. 1', 2, 1)
  104. IF(N .LT. 1) RETURN
  105. IF(N .EQ. 1 .AND. JOB .EQ. 0) GO TO 35
  106. MDIM = 2 * LDA
  107. IF(JOB .EQ. 0) GO TO 5
  108. IF (N .GT. LDV) CALL XERMSG ('SLATEC', 'CGEEV',
  109. + 'JOB .NE. 0 AND N .GT. LDV.', 3, 1)
  110. IF(N .GT. LDV) RETURN
  111. IF(N .EQ. 1) GO TO 35
  112. C
  113. C REARRANGE A IF NECESSARY WHEN LDA.GT.LDV AND JOB .NE.0
  114. C
  115. MDIM = MIN(MDIM,2 * LDV)
  116. IF (LDA .LT. LDV) CALL XERMSG ('SLATEC', 'CGEEV',
  117. + 'LDA.LT.LDV, ELEMENTS OF V OTHER THAN THE N BY N OUTPUT ' //
  118. + 'ELEMENTS HAVE BEEN CHANGED.', 5, 0)
  119. IF(LDA.LE.LDV) GO TO 5
  120. CALL XERMSG ('SLATEC', 'CGEEV',
  121. + 'LDA.GT.LDV, ELEMENTS OF A OTHER THAN THE N BY N INPUT ' //
  122. + 'ELEMENTS HAVE BEEN CHANGED.', 4, 0)
  123. L = N - 1
  124. DO 4 J=1,L
  125. I = 2 * N
  126. M = 1+J*2*LDV
  127. K = 1+J*2*LDA
  128. CALL SCOPY(I,A(K),1,A(M),1)
  129. 4 CONTINUE
  130. 5 CONTINUE
  131. C
  132. C SEPARATE REAL AND IMAGINARY PARTS
  133. C
  134. DO 6 J = 1, N
  135. K = (J-1) * MDIM +1
  136. L = K + N
  137. CALL SCOPY(N,A(K+1),2,WORK(1),1)
  138. CALL SCOPY(N,A(K),2,A(K),1)
  139. CALL SCOPY(N,WORK(1),1,A(L),1)
  140. 6 CONTINUE
  141. C
  142. C SCALE AND ORTHOGONAL REDUCTION TO HESSENBERG.
  143. C
  144. CALL CBAL(MDIM,N,A(1),A(N+1),ILO,IHI,WORK(1))
  145. CALL CORTH(MDIM,N,ILO,IHI,A(1),A(N+1),WORK(N+1),WORK(2*N+1))
  146. IF(JOB .NE. 0) GO TO 10
  147. C
  148. C EIGENVALUES ONLY
  149. C
  150. CALL COMQR(MDIM,N,ILO,IHI,A(1),A(N+1),E(1),E(N+1),INFO)
  151. GO TO 30
  152. C
  153. C EIGENVALUES AND EIGENVECTORS.
  154. C
  155. 10 CALL COMQR2(MDIM,N,ILO,IHI,WORK(N+1),WORK(2*N+1),A(1),A(N+1),
  156. 1 E(1),E(N+1),V(1),V(N+1),INFO)
  157. IF (INFO .NE. 0) GO TO 30
  158. CALL CBABK2(MDIM,N,ILO,IHI,WORK(1),N,V(1),V(N+1))
  159. C
  160. C CONVERT EIGENVECTORS TO COMPLEX STORAGE.
  161. C
  162. DO 20 J = 1,N
  163. K = (J-1) * MDIM + 1
  164. I = (J-1) * 2 * LDV + 1
  165. L = K + N
  166. CALL SCOPY(N,V(K),1,WORK(1),1)
  167. CALL SCOPY(N,V(L),1,V(I+1),2)
  168. CALL SCOPY(N,WORK(1),1,V(I),2)
  169. 20 CONTINUE
  170. C
  171. C CONVERT EIGENVALUES TO COMPLEX STORAGE.
  172. C
  173. 30 CALL SCOPY(N,E(1),1,WORK(1),1)
  174. CALL SCOPY(N,E(N+1),1,E(2),2)
  175. CALL SCOPY(N,WORK(1),1,E(1),2)
  176. RETURN
  177. C
  178. C TAKE CARE OF N=1 CASE
  179. C
  180. 35 E(1) = A(1)
  181. E(2) = A(2)
  182. INFO = 0
  183. IF(JOB .EQ. 0) RETURN
  184. V(1) = A(1)
  185. V(2) = A(2)
  186. RETURN
  187. END