sgeev.f 6.6 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184
  1. *DECK SGEEV
  2. SUBROUTINE SGEEV (A, LDA, N, E, V, LDV, WORK, JOB, INFO)
  3. C***BEGIN PROLOGUE SGEEV
  4. C***PURPOSE Compute the eigenvalues and, optionally, the eigenvectors
  5. C of a real general matrix.
  6. C***LIBRARY SLATEC
  7. C***CATEGORY D4A2
  8. C***TYPE SINGLE PRECISION (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 SGEEV computes the eigenvalues and, optionally,
  17. C the eigenvectors of a general real matrix.
  18. C
  19. C Call Sequence Parameters-
  20. C (The values of parameters marked with * (star) will be changed
  21. C by SGEEV.)
  22. C
  23. C A* REAL(LDA,N)
  24. C real nonsymmetric input matrix.
  25. C
  26. C LDA INTEGER
  27. C set by the user to
  28. C the leading dimension of the real 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 SGEEV, 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 SGEEV, 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 (Note that if the input matrix A is nearly degenerate,
  45. C V may be badly conditioned, i.e., may 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(2N)
  55. C temporary storage vector. Contents changed by SGEEV.
  56. C
  57. C JOB INTEGER
  58. C set by the user to
  59. C = 0 eigenvalues only to be calculated by SGEEV.
  60. C Neither V nor LDV is 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 .GT. LDV, SGEEV changes all the
  64. C elements of A thru column N. If LDA < LDV,
  65. C SGEEV 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 SGEEV.
  68. C
  69. C INFO* INTEGER
  70. C on return from SGEEV 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 x N output elements have been changed.
  85. C
  86. C***REFERENCES (NONE)
  87. C***ROUTINES CALLED BALANC, BALBAK, HQR, HQR2, ORTHES, ORTRAN, SCOPY,
  88. C SCOPYM, XERMSG
  89. C***REVISION HISTORY (YYMMDD)
  90. C 800808 DATE WRITTEN
  91. C 890531 Changed all specific intrinsics to generic. (WRB)
  92. C 890531 REVISION DATE from Version 3.2
  93. C 891214 Prologue converted to Version 4.0 format. (BAB)
  94. C 900315 CALLs to XERROR changed to CALLs to XERMSG. (THJ)
  95. C 900326 Removed duplicate information from DESCRIPTION section.
  96. C (WRB)
  97. C***END PROLOGUE SGEEV
  98. INTEGER I,IHI,ILO,INFO,J,JB,JOB,K,KM,KP,L,LDA,LDV,
  99. 1 MDIM,N
  100. REAL A(*),E(*),WORK(*),V(*)
  101. C***FIRST EXECUTABLE STATEMENT SGEEV
  102. IF (N .GT. LDA) CALL XERMSG ('SLATEC', 'SGEEV', 'N .GT. LDA.', 1,
  103. + 1)
  104. IF (N .GT. LDA) RETURN
  105. IF (N .LT. 1) CALL XERMSG ('SLATEC', 'SGEEV', 'N .LT. 1', 2, 1)
  106. IF(N .LT. 1) RETURN
  107. IF(N .EQ. 1 .AND. JOB .EQ. 0) GO TO 35
  108. MDIM = LDA
  109. IF(JOB .EQ. 0) GO TO 5
  110. IF (N .GT. LDV) CALL XERMSG ('SLATEC', 'SGEEV',
  111. + 'JOB .NE. 0 AND N .GT. LDV.', 3, 1)
  112. IF(N .GT. LDV) RETURN
  113. IF(N .EQ. 1) GO TO 35
  114. C
  115. C REARRANGE A IF NECESSARY WHEN LDA.GT.LDV AND JOB .NE.0
  116. C
  117. MDIM = MIN(LDA,LDV)
  118. IF (LDA .LT. LDV) CALL XERMSG ('SLATEC', 'SGEEV',
  119. + 'LDA.LT.LDV, ELEMENTS OF V OTHER THAN THE N BY N OUTPUT ' //
  120. + 'ELEMENTS HAVE BEEN CHANGED.', 5, 0)
  121. IF(LDA.LE.LDV) GO TO 5
  122. CALL XERMSG ('SLATEC', 'SGEEV',
  123. + 'LDA.GT.LDV, ELEMENTS OF A OTHER THAN THE N BY N INPUT ' //
  124. + 'ELEMENTS HAVE BEEN CHANGED.', 4, 0)
  125. L = N - 1
  126. DO 4 J=1,L
  127. M = 1+J*LDV
  128. K = 1+J*LDA
  129. CALL SCOPY(N,A(K),1,A(M),1)
  130. 4 CONTINUE
  131. 5 CONTINUE
  132. C
  133. C SCALE AND ORTHOGONAL REDUCTION TO HESSENBERG.
  134. C
  135. CALL BALANC(MDIM,N,A,ILO,IHI,WORK(1))
  136. CALL ORTHES(MDIM,N,ILO,IHI,A,WORK(N+1))
  137. IF(JOB .NE. 0) GO TO 10
  138. C
  139. C EIGENVALUES ONLY
  140. C
  141. CALL HQR(LDA,N,ILO,IHI,A,E(1),E(N+1),INFO)
  142. GO TO 30
  143. C
  144. C EIGENVALUES AND EIGENVECTORS.
  145. C
  146. 10 CALL ORTRAN(MDIM,N,ILO,IHI,A,WORK(N+1),V)
  147. CALL HQR2(MDIM,N,ILO,IHI,A,E(1),E(N+1),V,INFO)
  148. IF (INFO .NE. 0) GO TO 30
  149. CALL BALBAK(MDIM,N,ILO,IHI,WORK(1),N,V)
  150. C
  151. C CONVERT EIGENVECTORS TO COMPLEX STORAGE.
  152. C
  153. DO 20 JB = 1,N
  154. J=N+1-JB
  155. I=N+J
  156. K=(J-1)*MDIM+1
  157. KP=K+MDIM
  158. KM=K-MDIM
  159. IF(E(I).GE.0.0E0) CALL SCOPY(N,V(K),1,WORK(1),2)
  160. IF(E(I).LT.0.0E0) CALL SCOPY(N,V(KM),1,WORK(1),2)
  161. IF(E(I).EQ.0.0E0) CALL SCOPY(N,0.0E0,0,WORK(2),2)
  162. IF(E(I).GT.0.0E0) CALL SCOPY(N,V(KP),1,WORK(2),2)
  163. IF(E(I).LT.0.0E0) CALL SCOPYM(N,V(K),1,WORK(2),2)
  164. L=2*(J-1)*LDV+1
  165. CALL SCOPY(2*N,WORK(1),1,V(L),1)
  166. 20 CONTINUE
  167. C
  168. C CONVERT EIGENVALUES TO COMPLEX STORAGE.
  169. C
  170. 30 CALL SCOPY(N,E(1),1,WORK(1),1)
  171. CALL SCOPY(N,E(N+1),1,E(2),2)
  172. CALL SCOPY(N,WORK(1),1,E(1),2)
  173. RETURN
  174. C
  175. C TAKE CARE OF N=1 CASE
  176. C
  177. 35 E(1) = A(1)
  178. E(2) = 0.E0
  179. INFO = 0
  180. IF(JOB .EQ. 0) RETURN
  181. V(1) = A(1)
  182. V(2) = 0.E0
  183. RETURN
  184. END