Statistiques
| Révision :

root / src / lapack / double / dlasd5.f @ 10

Historique | Voir | Annoter | Télécharger (5,1 ko)

1 1 pfleura2
      SUBROUTINE DLASD5( I, D, Z, DELTA, RHO, DSIGMA, WORK )
2 1 pfleura2
*
3 1 pfleura2
*  -- LAPACK auxiliary routine (version 3.2) --
4 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
5 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
6 1 pfleura2
*     November 2006
7 1 pfleura2
*
8 1 pfleura2
*     .. Scalar Arguments ..
9 1 pfleura2
      INTEGER            I
10 1 pfleura2
      DOUBLE PRECISION   DSIGMA, RHO
11 1 pfleura2
*     ..
12 1 pfleura2
*     .. Array Arguments ..
13 1 pfleura2
      DOUBLE PRECISION   D( 2 ), DELTA( 2 ), WORK( 2 ), Z( 2 )
14 1 pfleura2
*     ..
15 1 pfleura2
*
16 1 pfleura2
*  Purpose
17 1 pfleura2
*  =======
18 1 pfleura2
*
19 1 pfleura2
*  This subroutine computes the square root of the I-th eigenvalue
20 1 pfleura2
*  of a positive symmetric rank-one modification of a 2-by-2 diagonal
21 1 pfleura2
*  matrix
22 1 pfleura2
*
23 1 pfleura2
*             diag( D ) * diag( D ) +  RHO *  Z * transpose(Z) .
24 1 pfleura2
*
25 1 pfleura2
*  The diagonal entries in the array D are assumed to satisfy
26 1 pfleura2
*
27 1 pfleura2
*             0 <= D(i) < D(j)  for  i < j .
28 1 pfleura2
*
29 1 pfleura2
*  We also assume RHO > 0 and that the Euclidean norm of the vector
30 1 pfleura2
*  Z is one.
31 1 pfleura2
*
32 1 pfleura2
*  Arguments
33 1 pfleura2
*  =========
34 1 pfleura2
*
35 1 pfleura2
*  I      (input) INTEGER
36 1 pfleura2
*         The index of the eigenvalue to be computed.  I = 1 or I = 2.
37 1 pfleura2
*
38 1 pfleura2
*  D      (input) DOUBLE PRECISION array, dimension ( 2 )
39 1 pfleura2
*         The original eigenvalues.  We assume 0 <= D(1) < D(2).
40 1 pfleura2
*
41 1 pfleura2
*  Z      (input) DOUBLE PRECISION array, dimension ( 2 )
42 1 pfleura2
*         The components of the updating vector.
43 1 pfleura2
*
44 1 pfleura2
*  DELTA  (output) DOUBLE PRECISION array, dimension ( 2 )
45 1 pfleura2
*         Contains (D(j) - sigma_I) in its  j-th component.
46 1 pfleura2
*         The vector DELTA contains the information necessary
47 1 pfleura2
*         to construct the eigenvectors.
48 1 pfleura2
*
49 1 pfleura2
*  RHO    (input) DOUBLE PRECISION
50 1 pfleura2
*         The scalar in the symmetric updating formula.
51 1 pfleura2
*
52 1 pfleura2
*  DSIGMA (output) DOUBLE PRECISION
53 1 pfleura2
*         The computed sigma_I, the I-th updated eigenvalue.
54 1 pfleura2
*
55 1 pfleura2
*  WORK   (workspace) DOUBLE PRECISION array, dimension ( 2 )
56 1 pfleura2
*         WORK contains (D(j) + sigma_I) in its  j-th component.
57 1 pfleura2
*
58 1 pfleura2
*  Further Details
59 1 pfleura2
*  ===============
60 1 pfleura2
*
61 1 pfleura2
*  Based on contributions by
62 1 pfleura2
*     Ren-Cang Li, Computer Science Division, University of California
63 1 pfleura2
*     at Berkeley, USA
64 1 pfleura2
*
65 1 pfleura2
*  =====================================================================
66 1 pfleura2
*
67 1 pfleura2
*     .. Parameters ..
68 1 pfleura2
      DOUBLE PRECISION   ZERO, ONE, TWO, THREE, FOUR
69 1 pfleura2
      PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0, TWO = 2.0D+0,
70 1 pfleura2
     $                   THREE = 3.0D+0, FOUR = 4.0D+0 )
71 1 pfleura2
*     ..
72 1 pfleura2
*     .. Local Scalars ..
73 1 pfleura2
      DOUBLE PRECISION   B, C, DEL, DELSQ, TAU, W
74 1 pfleura2
*     ..
75 1 pfleura2
*     .. Intrinsic Functions ..
76 1 pfleura2
      INTRINSIC          ABS, SQRT
77 1 pfleura2
*     ..
78 1 pfleura2
*     .. Executable Statements ..
79 1 pfleura2
*
80 1 pfleura2
      DEL = D( 2 ) - D( 1 )
81 1 pfleura2
      DELSQ = DEL*( D( 2 )+D( 1 ) )
82 1 pfleura2
      IF( I.EQ.1 ) THEN
83 1 pfleura2
         W = ONE + FOUR*RHO*( Z( 2 )*Z( 2 ) / ( D( 1 )+THREE*D( 2 ) )-
84 1 pfleura2
     $       Z( 1 )*Z( 1 ) / ( THREE*D( 1 )+D( 2 ) ) ) / DEL
85 1 pfleura2
         IF( W.GT.ZERO ) THEN
86 1 pfleura2
            B = DELSQ + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
87 1 pfleura2
            C = RHO*Z( 1 )*Z( 1 )*DELSQ
88 1 pfleura2
*
89 1 pfleura2
*           B > ZERO, always
90 1 pfleura2
*
91 1 pfleura2
*           The following TAU is DSIGMA * DSIGMA - D( 1 ) * D( 1 )
92 1 pfleura2
*
93 1 pfleura2
            TAU = TWO*C / ( B+SQRT( ABS( B*B-FOUR*C ) ) )
94 1 pfleura2
*
95 1 pfleura2
*           The following TAU is DSIGMA - D( 1 )
96 1 pfleura2
*
97 1 pfleura2
            TAU = TAU / ( D( 1 )+SQRT( D( 1 )*D( 1 )+TAU ) )
98 1 pfleura2
            DSIGMA = D( 1 ) + TAU
99 1 pfleura2
            DELTA( 1 ) = -TAU
100 1 pfleura2
            DELTA( 2 ) = DEL - TAU
101 1 pfleura2
            WORK( 1 ) = TWO*D( 1 ) + TAU
102 1 pfleura2
            WORK( 2 ) = ( D( 1 )+TAU ) + D( 2 )
103 1 pfleura2
*           DELTA( 1 ) = -Z( 1 ) / TAU
104 1 pfleura2
*           DELTA( 2 ) = Z( 2 ) / ( DEL-TAU )
105 1 pfleura2
         ELSE
106 1 pfleura2
            B = -DELSQ + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
107 1 pfleura2
            C = RHO*Z( 2 )*Z( 2 )*DELSQ
108 1 pfleura2
*
109 1 pfleura2
*           The following TAU is DSIGMA * DSIGMA - D( 2 ) * D( 2 )
110 1 pfleura2
*
111 1 pfleura2
            IF( B.GT.ZERO ) THEN
112 1 pfleura2
               TAU = -TWO*C / ( B+SQRT( B*B+FOUR*C ) )
113 1 pfleura2
            ELSE
114 1 pfleura2
               TAU = ( B-SQRT( B*B+FOUR*C ) ) / TWO
115 1 pfleura2
            END IF
116 1 pfleura2
*
117 1 pfleura2
*           The following TAU is DSIGMA - D( 2 )
118 1 pfleura2
*
119 1 pfleura2
            TAU = TAU / ( D( 2 )+SQRT( ABS( D( 2 )*D( 2 )+TAU ) ) )
120 1 pfleura2
            DSIGMA = D( 2 ) + TAU
121 1 pfleura2
            DELTA( 1 ) = -( DEL+TAU )
122 1 pfleura2
            DELTA( 2 ) = -TAU
123 1 pfleura2
            WORK( 1 ) = D( 1 ) + TAU + D( 2 )
124 1 pfleura2
            WORK( 2 ) = TWO*D( 2 ) + TAU
125 1 pfleura2
*           DELTA( 1 ) = -Z( 1 ) / ( DEL+TAU )
126 1 pfleura2
*           DELTA( 2 ) = -Z( 2 ) / TAU
127 1 pfleura2
         END IF
128 1 pfleura2
*        TEMP = SQRT( DELTA( 1 )*DELTA( 1 )+DELTA( 2 )*DELTA( 2 ) )
129 1 pfleura2
*        DELTA( 1 ) = DELTA( 1 ) / TEMP
130 1 pfleura2
*        DELTA( 2 ) = DELTA( 2 ) / TEMP
131 1 pfleura2
      ELSE
132 1 pfleura2
*
133 1 pfleura2
*        Now I=2
134 1 pfleura2
*
135 1 pfleura2
         B = -DELSQ + RHO*( Z( 1 )*Z( 1 )+Z( 2 )*Z( 2 ) )
136 1 pfleura2
         C = RHO*Z( 2 )*Z( 2 )*DELSQ
137 1 pfleura2
*
138 1 pfleura2
*        The following TAU is DSIGMA * DSIGMA - D( 2 ) * D( 2 )
139 1 pfleura2
*
140 1 pfleura2
         IF( B.GT.ZERO ) THEN
141 1 pfleura2
            TAU = ( B+SQRT( B*B+FOUR*C ) ) / TWO
142 1 pfleura2
         ELSE
143 1 pfleura2
            TAU = TWO*C / ( -B+SQRT( B*B+FOUR*C ) )
144 1 pfleura2
         END IF
145 1 pfleura2
*
146 1 pfleura2
*        The following TAU is DSIGMA - D( 2 )
147 1 pfleura2
*
148 1 pfleura2
         TAU = TAU / ( D( 2 )+SQRT( D( 2 )*D( 2 )+TAU ) )
149 1 pfleura2
         DSIGMA = D( 2 ) + TAU
150 1 pfleura2
         DELTA( 1 ) = -( DEL+TAU )
151 1 pfleura2
         DELTA( 2 ) = -TAU
152 1 pfleura2
         WORK( 1 ) = D( 1 ) + TAU + D( 2 )
153 1 pfleura2
         WORK( 2 ) = TWO*D( 2 ) + TAU
154 1 pfleura2
*        DELTA( 1 ) = -Z( 1 ) / ( DEL+TAU )
155 1 pfleura2
*        DELTA( 2 ) = -Z( 2 ) / TAU
156 1 pfleura2
*        TEMP = SQRT( DELTA( 1 )*DELTA( 1 )+DELTA( 2 )*DELTA( 2 ) )
157 1 pfleura2
*        DELTA( 1 ) = DELTA( 1 ) / TEMP
158 1 pfleura2
*        DELTA( 2 ) = DELTA( 2 ) / TEMP
159 1 pfleura2
      END IF
160 1 pfleura2
      RETURN
161 1 pfleura2
*
162 1 pfleura2
*     End of DLASD5
163 1 pfleura2
*
164 1 pfleura2
      END