Statistiques
| Révision :

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

Historique | Voir | Annoter | Télécharger (8,6 ko)

1 1 pfleura2
      SUBROUTINE DLASD8( ICOMPQ, K, D, Z, VF, VL, DIFL, DIFR, LDDIFR,
2 1 pfleura2
     $                   DSIGMA, WORK, INFO )
3 1 pfleura2
*
4 1 pfleura2
*  -- LAPACK auxiliary routine (version 3.2.2) --
5 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
6 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
7 1 pfleura2
*     June 2010
8 1 pfleura2
*
9 1 pfleura2
*     .. Scalar Arguments ..
10 1 pfleura2
      INTEGER            ICOMPQ, INFO, K, LDDIFR
11 1 pfleura2
*     ..
12 1 pfleura2
*     .. Array Arguments ..
13 1 pfleura2
      DOUBLE PRECISION   D( * ), DIFL( * ), DIFR( LDDIFR, * ),
14 1 pfleura2
     $                   DSIGMA( * ), VF( * ), VL( * ), WORK( * ),
15 1 pfleura2
     $                   Z( * )
16 1 pfleura2
*     ..
17 1 pfleura2
*
18 1 pfleura2
*  Purpose
19 1 pfleura2
*  =======
20 1 pfleura2
*
21 1 pfleura2
*  DLASD8 finds the square roots of the roots of the secular equation,
22 1 pfleura2
*  as defined by the values in DSIGMA and Z. It makes the appropriate
23 1 pfleura2
*  calls to DLASD4, and stores, for each  element in D, the distance
24 1 pfleura2
*  to its two nearest poles (elements in DSIGMA). It also updates
25 1 pfleura2
*  the arrays VF and VL, the first and last components of all the
26 1 pfleura2
*  right singular vectors of the original bidiagonal matrix.
27 1 pfleura2
*
28 1 pfleura2
*  DLASD8 is called from DLASD6.
29 1 pfleura2
*
30 1 pfleura2
*  Arguments
31 1 pfleura2
*  =========
32 1 pfleura2
*
33 1 pfleura2
*  ICOMPQ  (input) INTEGER
34 1 pfleura2
*          Specifies whether singular vectors are to be computed in
35 1 pfleura2
*          factored form in the calling routine:
36 1 pfleura2
*          = 0: Compute singular values only.
37 1 pfleura2
*          = 1: Compute singular vectors in factored form as well.
38 1 pfleura2
*
39 1 pfleura2
*  K       (input) INTEGER
40 1 pfleura2
*          The number of terms in the rational function to be solved
41 1 pfleura2
*          by DLASD4.  K >= 1.
42 1 pfleura2
*
43 1 pfleura2
*  D       (output) DOUBLE PRECISION array, dimension ( K )
44 1 pfleura2
*          On output, D contains the updated singular values.
45 1 pfleura2
*
46 1 pfleura2
*  Z       (input/output) DOUBLE PRECISION array, dimension ( K )
47 1 pfleura2
*          On entry, the first K elements of this array contain the
48 1 pfleura2
*          components of the deflation-adjusted updating row vector.
49 1 pfleura2
*          On exit, Z is updated.
50 1 pfleura2
*
51 1 pfleura2
*  VF      (input/output) DOUBLE PRECISION array, dimension ( K )
52 1 pfleura2
*          On entry, VF contains  information passed through DBEDE8.
53 1 pfleura2
*          On exit, VF contains the first K components of the first
54 1 pfleura2
*          components of all right singular vectors of the bidiagonal
55 1 pfleura2
*          matrix.
56 1 pfleura2
*
57 1 pfleura2
*  VL      (input/output) DOUBLE PRECISION array, dimension ( K )
58 1 pfleura2
*          On entry, VL contains  information passed through DBEDE8.
59 1 pfleura2
*          On exit, VL contains the first K components of the last
60 1 pfleura2
*          components of all right singular vectors of the bidiagonal
61 1 pfleura2
*          matrix.
62 1 pfleura2
*
63 1 pfleura2
*  DIFL    (output) DOUBLE PRECISION array, dimension ( K )
64 1 pfleura2
*          On exit, DIFL(I) = D(I) - DSIGMA(I).
65 1 pfleura2
*
66 1 pfleura2
*  DIFR    (output) DOUBLE PRECISION array,
67 1 pfleura2
*                   dimension ( LDDIFR, 2 ) if ICOMPQ = 1 and
68 1 pfleura2
*                   dimension ( K ) if ICOMPQ = 0.
69 1 pfleura2
*          On exit, DIFR(I,1) = D(I) - DSIGMA(I+1), DIFR(K,1) is not
70 1 pfleura2
*          defined and will not be referenced.
71 1 pfleura2
*
72 1 pfleura2
*          If ICOMPQ = 1, DIFR(1:K,2) is an array containing the
73 1 pfleura2
*          normalizing factors for the right singular vector matrix.
74 1 pfleura2
*
75 1 pfleura2
*  LDDIFR  (input) INTEGER
76 1 pfleura2
*          The leading dimension of DIFR, must be at least K.
77 1 pfleura2
*
78 1 pfleura2
*  DSIGMA  (input/output) DOUBLE PRECISION array, dimension ( K )
79 1 pfleura2
*          On entry, the first K elements of this array contain the old
80 1 pfleura2
*          roots of the deflated updating problem.  These are the poles
81 1 pfleura2
*          of the secular equation.
82 1 pfleura2
*          On exit, the elements of DSIGMA may be very slightly altered
83 1 pfleura2
*          in value.
84 1 pfleura2
*
85 1 pfleura2
*  WORK    (workspace) DOUBLE PRECISION array, dimension at least 3 * K
86 1 pfleura2
*
87 1 pfleura2
*  INFO    (output) INTEGER
88 1 pfleura2
*          = 0:  successful exit.
89 1 pfleura2
*          < 0:  if INFO = -i, the i-th argument had an illegal value.
90 1 pfleura2
*          > 0:  if INFO = 1, a singular value did not converge
91 1 pfleura2
*
92 1 pfleura2
*  Further Details
93 1 pfleura2
*  ===============
94 1 pfleura2
*
95 1 pfleura2
*  Based on contributions by
96 1 pfleura2
*     Ming Gu and Huan Ren, Computer Science Division, University of
97 1 pfleura2
*     California at Berkeley, USA
98 1 pfleura2
*
99 1 pfleura2
*  =====================================================================
100 1 pfleura2
*
101 1 pfleura2
*     .. Parameters ..
102 1 pfleura2
      DOUBLE PRECISION   ONE
103 1 pfleura2
      PARAMETER          ( ONE = 1.0D+0 )
104 1 pfleura2
*     ..
105 1 pfleura2
*     .. Local Scalars ..
106 1 pfleura2
      INTEGER            I, IWK1, IWK2, IWK2I, IWK3, IWK3I, J
107 1 pfleura2
      DOUBLE PRECISION   DIFLJ, DIFRJ, DJ, DSIGJ, DSIGJP, RHO, TEMP
108 1 pfleura2
*     ..
109 1 pfleura2
*     .. External Subroutines ..
110 1 pfleura2
      EXTERNAL           DCOPY, DLASCL, DLASD4, DLASET, XERBLA
111 1 pfleura2
*     ..
112 1 pfleura2
*     .. External Functions ..
113 1 pfleura2
      DOUBLE PRECISION   DDOT, DLAMC3, DNRM2
114 1 pfleura2
      EXTERNAL           DDOT, DLAMC3, DNRM2
115 1 pfleura2
*     ..
116 1 pfleura2
*     .. Intrinsic Functions ..
117 1 pfleura2
      INTRINSIC          ABS, SIGN, SQRT
118 1 pfleura2
*     ..
119 1 pfleura2
*     .. Executable Statements ..
120 1 pfleura2
*
121 1 pfleura2
*     Test the input parameters.
122 1 pfleura2
*
123 1 pfleura2
      INFO = 0
124 1 pfleura2
*
125 1 pfleura2
      IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
126 1 pfleura2
         INFO = -1
127 1 pfleura2
      ELSE IF( K.LT.1 ) THEN
128 1 pfleura2
         INFO = -2
129 1 pfleura2
      ELSE IF( LDDIFR.LT.K ) THEN
130 1 pfleura2
         INFO = -9
131 1 pfleura2
      END IF
132 1 pfleura2
      IF( INFO.NE.0 ) THEN
133 1 pfleura2
         CALL XERBLA( 'DLASD8', -INFO )
134 1 pfleura2
         RETURN
135 1 pfleura2
      END IF
136 1 pfleura2
*
137 1 pfleura2
*     Quick return if possible
138 1 pfleura2
*
139 1 pfleura2
      IF( K.EQ.1 ) THEN
140 1 pfleura2
         D( 1 ) = ABS( Z( 1 ) )
141 1 pfleura2
         DIFL( 1 ) = D( 1 )
142 1 pfleura2
         IF( ICOMPQ.EQ.1 ) THEN
143 1 pfleura2
            DIFL( 2 ) = ONE
144 1 pfleura2
            DIFR( 1, 2 ) = ONE
145 1 pfleura2
         END IF
146 1 pfleura2
         RETURN
147 1 pfleura2
      END IF
148 1 pfleura2
*
149 1 pfleura2
*     Modify values DSIGMA(i) to make sure all DSIGMA(i)-DSIGMA(j) can
150 1 pfleura2
*     be computed with high relative accuracy (barring over/underflow).
151 1 pfleura2
*     This is a problem on machines without a guard digit in
152 1 pfleura2
*     add/subtract (Cray XMP, Cray YMP, Cray C 90 and Cray 2).
153 1 pfleura2
*     The following code replaces DSIGMA(I) by 2*DSIGMA(I)-DSIGMA(I),
154 1 pfleura2
*     which on any of these machines zeros out the bottommost
155 1 pfleura2
*     bit of DSIGMA(I) if it is 1; this makes the subsequent
156 1 pfleura2
*     subtractions DSIGMA(I)-DSIGMA(J) unproblematic when cancellation
157 1 pfleura2
*     occurs. On binary machines with a guard digit (almost all
158 1 pfleura2
*     machines) it does not change DSIGMA(I) at all. On hexadecimal
159 1 pfleura2
*     and decimal machines with a guard digit, it slightly
160 1 pfleura2
*     changes the bottommost bits of DSIGMA(I). It does not account
161 1 pfleura2
*     for hexadecimal or decimal machines without guard digits
162 1 pfleura2
*     (we know of none). We use a subroutine call to compute
163 1 pfleura2
*     2*DLAMBDA(I) to prevent optimizing compilers from eliminating
164 1 pfleura2
*     this code.
165 1 pfleura2
*
166 1 pfleura2
      DO 10 I = 1, K
167 1 pfleura2
         DSIGMA( I ) = DLAMC3( DSIGMA( I ), DSIGMA( I ) ) - DSIGMA( I )
168 1 pfleura2
   10 CONTINUE
169 1 pfleura2
*
170 1 pfleura2
*     Book keeping.
171 1 pfleura2
*
172 1 pfleura2
      IWK1 = 1
173 1 pfleura2
      IWK2 = IWK1 + K
174 1 pfleura2
      IWK3 = IWK2 + K
175 1 pfleura2
      IWK2I = IWK2 - 1
176 1 pfleura2
      IWK3I = IWK3 - 1
177 1 pfleura2
*
178 1 pfleura2
*     Normalize Z.
179 1 pfleura2
*
180 1 pfleura2
      RHO = DNRM2( K, Z, 1 )
181 1 pfleura2
      CALL DLASCL( 'G', 0, 0, RHO, ONE, K, 1, Z, K, INFO )
182 1 pfleura2
      RHO = RHO*RHO
183 1 pfleura2
*
184 1 pfleura2
*     Initialize WORK(IWK3).
185 1 pfleura2
*
186 1 pfleura2
      CALL DLASET( 'A', K, 1, ONE, ONE, WORK( IWK3 ), K )
187 1 pfleura2
*
188 1 pfleura2
*     Compute the updated singular values, the arrays DIFL, DIFR,
189 1 pfleura2
*     and the updated Z.
190 1 pfleura2
*
191 1 pfleura2
      DO 40 J = 1, K
192 1 pfleura2
         CALL DLASD4( K, J, DSIGMA, Z, WORK( IWK1 ), RHO, D( J ),
193 1 pfleura2
     $                WORK( IWK2 ), INFO )
194 1 pfleura2
*
195 1 pfleura2
*        If the root finder fails, the computation is terminated.
196 1 pfleura2
*
197 1 pfleura2
         IF( INFO.NE.0 ) THEN
198 1 pfleura2
            RETURN
199 1 pfleura2
         END IF
200 1 pfleura2
         WORK( IWK3I+J ) = WORK( IWK3I+J )*WORK( J )*WORK( IWK2I+J )
201 1 pfleura2
         DIFL( J ) = -WORK( J )
202 1 pfleura2
         DIFR( J, 1 ) = -WORK( J+1 )
203 1 pfleura2
         DO 20 I = 1, J - 1
204 1 pfleura2
            WORK( IWK3I+I ) = WORK( IWK3I+I )*WORK( I )*
205 1 pfleura2
     $                        WORK( IWK2I+I ) / ( DSIGMA( I )-
206 1 pfleura2
     $                        DSIGMA( J ) ) / ( DSIGMA( I )+
207 1 pfleura2
     $                        DSIGMA( J ) )
208 1 pfleura2
   20    CONTINUE
209 1 pfleura2
         DO 30 I = J + 1, K
210 1 pfleura2
            WORK( IWK3I+I ) = WORK( IWK3I+I )*WORK( I )*
211 1 pfleura2
     $                        WORK( IWK2I+I ) / ( DSIGMA( I )-
212 1 pfleura2
     $                        DSIGMA( J ) ) / ( DSIGMA( I )+
213 1 pfleura2
     $                        DSIGMA( J ) )
214 1 pfleura2
   30    CONTINUE
215 1 pfleura2
   40 CONTINUE
216 1 pfleura2
*
217 1 pfleura2
*     Compute updated Z.
218 1 pfleura2
*
219 1 pfleura2
      DO 50 I = 1, K
220 1 pfleura2
         Z( I ) = SIGN( SQRT( ABS( WORK( IWK3I+I ) ) ), Z( I ) )
221 1 pfleura2
   50 CONTINUE
222 1 pfleura2
*
223 1 pfleura2
*     Update VF and VL.
224 1 pfleura2
*
225 1 pfleura2
      DO 80 J = 1, K
226 1 pfleura2
         DIFLJ = DIFL( J )
227 1 pfleura2
         DJ = D( J )
228 1 pfleura2
         DSIGJ = -DSIGMA( J )
229 1 pfleura2
         IF( J.LT.K ) THEN
230 1 pfleura2
            DIFRJ = -DIFR( J, 1 )
231 1 pfleura2
            DSIGJP = -DSIGMA( J+1 )
232 1 pfleura2
         END IF
233 1 pfleura2
         WORK( J ) = -Z( J ) / DIFLJ / ( DSIGMA( J )+DJ )
234 1 pfleura2
         DO 60 I = 1, J - 1
235 1 pfleura2
            WORK( I ) = Z( I ) / ( DLAMC3( DSIGMA( I ), DSIGJ )-DIFLJ )
236 1 pfleura2
     $                   / ( DSIGMA( I )+DJ )
237 1 pfleura2
   60    CONTINUE
238 1 pfleura2
         DO 70 I = J + 1, K
239 1 pfleura2
            WORK( I ) = Z( I ) / ( DLAMC3( DSIGMA( I ), DSIGJP )+DIFRJ )
240 1 pfleura2
     $                   / ( DSIGMA( I )+DJ )
241 1 pfleura2
   70    CONTINUE
242 1 pfleura2
         TEMP = DNRM2( K, WORK, 1 )
243 1 pfleura2
         WORK( IWK2I+J ) = DDOT( K, WORK, 1, VF, 1 ) / TEMP
244 1 pfleura2
         WORK( IWK3I+J ) = DDOT( K, WORK, 1, VL, 1 ) / TEMP
245 1 pfleura2
         IF( ICOMPQ.EQ.1 ) THEN
246 1 pfleura2
            DIFR( J, 2 ) = TEMP
247 1 pfleura2
         END IF
248 1 pfleura2
   80 CONTINUE
249 1 pfleura2
*
250 1 pfleura2
      CALL DCOPY( K, WORK( IWK2 ), 1, VF, 1 )
251 1 pfleura2
      CALL DCOPY( K, WORK( IWK3 ), 1, VL, 1 )
252 1 pfleura2
*
253 1 pfleura2
      RETURN
254 1 pfleura2
*
255 1 pfleura2
*     End of DLASD8
256 1 pfleura2
*
257 1 pfleura2
      END