~ubuntu-branches/debian/sid/octave3.0/sid

« back to all changes in this revision

Viewing changes to libcruft/lapack/dlasd5.f

  • Committer: Bazaar Package Importer
  • Author(s): Rafael Laboissiere
  • Date: 2007-12-23 16:04:15 UTC
  • Revision ID: james.westby@ubuntu.com-20071223160415-n4gk468dihy22e9v
Tags: upstream-3.0.0
ImportĀ upstreamĀ versionĀ 3.0.0

Show diffs side-by-side

added added

removed removed

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