Change Eclipse configuration
[jabaws.git] / website / archive / binaries / mac / src / disembl / Tisean_3.0.1 / source_f / slatec / tred1.f
1 *DECK TRED1
2       SUBROUTINE TRED1 (NM, N, A, D, E, E2)
3 C***BEGIN PROLOGUE  TRED1
4 C***PURPOSE  Reduce a real symmetric matrix to symmetric tridiagonal
5 C            matrix using orthogonal similarity transformations.
6 C***LIBRARY   SLATEC (EISPACK)
7 C***CATEGORY  D4C1B1
8 C***TYPE      SINGLE PRECISION (TRED1-S)
9 C***KEYWORDS  EIGENVALUES, EIGENVECTORS, EISPACK
10 C***AUTHOR  Smith, B. T., et al.
11 C***DESCRIPTION
12 C
13 C     This subroutine is a translation of the ALGOL procedure TRED1,
14 C     NUM. MATH. 11, 181-195(1968) by Martin, Reinsch, and Wilkinson.
15 C     HANDBOOK FOR AUTO. COMP., VOL.II-LINEAR ALGEBRA, 212-226(1971).
16 C
17 C     This subroutine reduces a REAL SYMMETRIC matrix
18 C     to a symmetric tridiagonal matrix using
19 C     orthogonal similarity transformations.
20 C
21 C     On Input
22 C
23 C        NM must be set to the row dimension of the two-dimensional
24 C          array parameter, A, as declared in the calling program
25 C          dimension statement.  NM is an INTEGER variable.
26 C
27 C        N is the order of the matrix A.  N is an INTEGER variable.
28 C          N must be less than or equal to NM.
29 C
30 C        A contains the real symmetric input matrix.  Only the lower
31 C          triangle of the matrix need be supplied.  A is a two-
32 C          dimensional REAL array, dimensioned A(NM,N).
33 C
34 C     On Output
35 C
36 C        A contains information about the orthogonal transformations
37 C          used in the reduction in its strict lower triangle.  The
38 C          full upper triangle of A is unaltered.
39 C
40 C        D contains the diagonal elements of the symmetric tridiagonal
41 C          matrix.  D is a one-dimensional REAL array, dimensioned D(N).
42 C
43 C        E contains the subdiagonal elements of the symmetric
44 C          tridiagonal matrix in its last N-1 positions.  E(1) is set
45 C          to zero.  E is a one-dimensional REAL array, dimensioned
46 C          E(N).
47 C
48 C        E2 contains the squares of the corresponding elements of E.
49 C          E2 may coincide with E if the squares are not needed.
50 C          E2 is a one-dimensional REAL array, dimensioned E2(N).
51 C
52 C     Questions and comments should be directed to B. S. Garbow,
53 C     APPLIED MATHEMATICS DIVISION, ARGONNE NATIONAL LABORATORY
54 C     ------------------------------------------------------------------
55 C
56 C***REFERENCES  B. T. Smith, J. M. Boyle, J. J. Dongarra, B. S. Garbow,
57 C                 Y. Ikebe, V. C. Klema and C. B. Moler, Matrix Eigen-
58 C                 system Routines - EISPACK Guide, Springer-Verlag,
59 C                 1976.
60 C***ROUTINES CALLED  (NONE)
61 C***REVISION HISTORY  (YYMMDD)
62 C   760101  DATE WRITTEN
63 C   890831  Modified array declarations.  (WRB)
64 C   890831  REVISION DATE from Version 3.2
65 C   891214  Prologue converted to Version 4.0 format.  (BAB)
66 C   920501  Reformatted the REFERENCES section.  (WRB)
67 C***END PROLOGUE  TRED1
68 C
69       INTEGER I,J,K,L,N,II,NM,JP1
70       REAL A(NM,*),D(*),E(*),E2(*)
71       REAL F,G,H,SCALE
72 C
73 C***FIRST EXECUTABLE STATEMENT  TRED1
74       DO 100 I = 1, N
75   100 D(I) = A(I,I)
76 C     .......... FOR I=N STEP -1 UNTIL 1 DO -- ..........
77       DO 300 II = 1, N
78          I = N + 1 - II
79          L = I - 1
80          H = 0.0E0
81          SCALE = 0.0E0
82          IF (L .LT. 1) GO TO 130
83 C     .......... SCALE ROW (ALGOL TOL THEN NOT NEEDED) ..........
84          DO 120 K = 1, L
85   120    SCALE = SCALE + ABS(A(I,K))
86 C
87          IF (SCALE .NE. 0.0E0) GO TO 140
88   130    E(I) = 0.0E0
89          E2(I) = 0.0E0
90          GO TO 290
91 C
92   140    DO 150 K = 1, L
93             A(I,K) = A(I,K) / SCALE
94             H = H + A(I,K) * A(I,K)
95   150    CONTINUE
96 C
97          E2(I) = SCALE * SCALE * H
98          F = A(I,L)
99          G = -SIGN(SQRT(H),F)
100          E(I) = SCALE * G
101          H = H - F * G
102          A(I,L) = F - G
103          IF (L .EQ. 1) GO TO 270
104          F = 0.0E0
105 C
106          DO 240 J = 1, L
107             G = 0.0E0
108 C     .......... FORM ELEMENT OF A*U ..........
109             DO 180 K = 1, J
110   180       G = G + A(J,K) * A(I,K)
111 C
112             JP1 = J + 1
113             IF (L .LT. JP1) GO TO 220
114 C
115             DO 200 K = JP1, L
116   200       G = G + A(K,J) * A(I,K)
117 C     .......... FORM ELEMENT OF P ..........
118   220       E(J) = G / H
119             F = F + E(J) * A(I,J)
120   240    CONTINUE
121 C
122          H = F / (H + H)
123 C     .......... FORM REDUCED A ..........
124          DO 260 J = 1, L
125             F = A(I,J)
126             G = E(J) - H * F
127             E(J) = G
128 C
129             DO 260 K = 1, J
130                A(J,K) = A(J,K) - F * E(K) - G * A(I,K)
131   260    CONTINUE
132 C
133   270    DO 280 K = 1, L
134   280    A(I,K) = SCALE * A(I,K)
135 C
136   290    H = D(I)
137          D(I) = A(I,I)
138          A(I,I) = H
139   300 CONTINUE
140 C
141       RETURN
142       END