Change Eclipse configuration
[jabaws.git] / website / archive / binaries / mac / src / disembl / Tisean_3.0.1 / source_f / slatec / rs.f
1 *DECK RS
2       SUBROUTINE RS (NM, N, A, W, MATZ, Z, FV1, FV2, IERR)
3 C***BEGIN PROLOGUE  RS
4 C***PURPOSE  Compute the eigenvalues and, optionally, the eigenvectors
5 C            of a real symmetric matrix.
6 C***LIBRARY   SLATEC (EISPACK)
7 C***CATEGORY  D4A1
8 C***TYPE      SINGLE PRECISION (RS-S, CH-C)
9 C***KEYWORDS  EIGENVALUES, EIGENVECTORS, EISPACK
10 C***AUTHOR  Smith, B. T., et al.
11 C***DESCRIPTION
12 C
13 C     This subroutine calls the recommended sequence of
14 C     subroutines from the eigensystem subroutine package (EISPACK)
15 C     to find the eigenvalues and eigenvectors (if desired)
16 C     of a REAL SYMMETRIC matrix.
17 C
18 C     On Input
19 C
20 C        NM must be set to the row dimension of the two-dimensional
21 C          array parameters, A and Z, as declared in the calling
22 C          program dimension statement.  NM is an INTEGER variable.
23 C
24 C        N is the order of the matrix A.  N is an INTEGER variable.
25 C          N must be less than or equal to NM.
26 C
27 C        A contains the real symmetric matrix.  A is a two-dimensional
28 C          REAL array, dimensioned A(NM,N).
29 C
30 C        MATZ is an INTEGER variable set equal to zero if only
31 C          eigenvalues are desired.  Otherwise, it is set to any
32 C          non-zero integer for both eigenvalues and eigenvectors.
33 C
34 C     On Output
35 C
36 C        A is unaltered.
37 C
38 C        W contains the eigenvalues in ascending order.  W is a one-
39 C          dimensional REAL array, dimensioned W(N).
40 C
41 C        Z contains the eigenvectors if MATZ is not zero.  The
42 C          eigenvectors are orthonormal.  Z is a two-dimensional
43 C          REAL array, dimensioned Z(NM,N).
44 C
45 C        IERR is an INTEGER flag set to
46 C          Zero       for normal return,
47 C          10*N       if N is greater than NM,
48 C          J          if the J-th eigenvalue has not been
49 C                     determined after 30 iterations.
50 C                     The eigenvalues, and eigenvectors if requested,
51 C                     should be correct for indices 1, 2, ..., IERR-1.
52 C
53 C        FV1 and FV2 are one-dimensional REAL arrays used for temporary
54 C          storage, dimensioned FV1(N) and FV2(N).
55 C
56 C     Questions and comments should be directed to B. S. Garbow,
57 C     APPLIED MATHEMATICS DIVISION, ARGONNE NATIONAL LABORATORY
58 C     ------------------------------------------------------------------
59 C
60 C***REFERENCES  B. T. Smith, J. M. Boyle, J. J. Dongarra, B. S. Garbow,
61 C                 Y. Ikebe, V. C. Klema and C. B. Moler, Matrix Eigen-
62 C                 system Routines - EISPACK Guide, Springer-Verlag,
63 C                 1976.
64 C***ROUTINES CALLED  TQL2, TQLRAT, TRED1, TRED2
65 C***REVISION HISTORY  (YYMMDD)
66 C   760101  DATE WRITTEN
67 C   890831  Modified array declarations.  (WRB)
68 C   890831  REVISION DATE from Version 3.2
69 C   891214  Prologue converted to Version 4.0 format.  (BAB)
70 C   920501  Reformatted the REFERENCES section.  (WRB)
71 C***END PROLOGUE  RS
72 C
73       INTEGER N,NM,IERR,MATZ
74       REAL A(NM,*),W(*),Z(NM,*),FV1(*),FV2(*)
75 C
76 C***FIRST EXECUTABLE STATEMENT  RS
77       IF (N .LE. NM) GO TO 10
78       IERR = 10 * N
79       GO TO 50
80 C
81    10 IF (MATZ .NE. 0) GO TO 20
82 C     .......... FIND EIGENVALUES ONLY ..........
83       CALL  TRED1(NM,N,A,W,FV1,FV2)
84       CALL  TQLRAT(N,W,FV2,IERR)
85       GO TO 50
86 C     .......... FIND BOTH EIGENVALUES AND EIGENVECTORS ..........
87    20 CALL  TRED2(NM,N,A,W,FV1,Z)
88       CALL  TQL2(NM,N,W,FV1,Z,IERR)
89    50 RETURN
90       END