Statistiques
| Révision :

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

Historique | Voir | Annoter | Télécharger (11,05 ko)

1 1 pfleura2
      SUBROUTINE DLASD6( ICOMPQ, NL, NR, SQRE, D, VF, VL, ALPHA, BETA,
2 1 pfleura2
     $                   IDXQ, PERM, GIVPTR, GIVCOL, LDGCOL, GIVNUM,
3 1 pfleura2
     $                   LDGNUM, POLES, DIFL, DIFR, Z, K, C, S, WORK,
4 1 pfleura2
     $                   IWORK, INFO )
5 1 pfleura2
*
6 1 pfleura2
*  -- LAPACK auxiliary routine (version 3.2.2) --
7 1 pfleura2
*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
8 1 pfleura2
*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
9 1 pfleura2
*     June 2010
10 1 pfleura2
*
11 1 pfleura2
*     .. Scalar Arguments ..
12 1 pfleura2
      INTEGER            GIVPTR, ICOMPQ, INFO, K, LDGCOL, LDGNUM, NL,
13 1 pfleura2
     $                   NR, SQRE
14 1 pfleura2
      DOUBLE PRECISION   ALPHA, BETA, C, S
15 1 pfleura2
*     ..
16 1 pfleura2
*     .. Array Arguments ..
17 1 pfleura2
      INTEGER            GIVCOL( LDGCOL, * ), IDXQ( * ), IWORK( * ),
18 1 pfleura2
     $                   PERM( * )
19 1 pfleura2
      DOUBLE PRECISION   D( * ), DIFL( * ), DIFR( * ),
20 1 pfleura2
     $                   GIVNUM( LDGNUM, * ), POLES( LDGNUM, * ),
21 1 pfleura2
     $                   VF( * ), VL( * ), WORK( * ), Z( * )
22 1 pfleura2
*     ..
23 1 pfleura2
*
24 1 pfleura2
*  Purpose
25 1 pfleura2
*  =======
26 1 pfleura2
*
27 1 pfleura2
*  DLASD6 computes the SVD of an updated upper bidiagonal matrix B
28 1 pfleura2
*  obtained by merging two smaller ones by appending a row. This
29 1 pfleura2
*  routine is used only for the problem which requires all singular
30 1 pfleura2
*  values and optionally singular vector matrices in factored form.
31 1 pfleura2
*  B is an N-by-M matrix with N = NL + NR + 1 and M = N + SQRE.
32 1 pfleura2
*  A related subroutine, DLASD1, handles the case in which all singular
33 1 pfleura2
*  values and singular vectors of the bidiagonal matrix are desired.
34 1 pfleura2
*
35 1 pfleura2
*  DLASD6 computes the SVD as follows:
36 1 pfleura2
*
37 1 pfleura2
*                ( D1(in)  0    0     0 )
38 1 pfleura2
*    B = U(in) * (   Z1'   a   Z2'    b ) * VT(in)
39 1 pfleura2
*                (   0     0   D2(in) 0 )
40 1 pfleura2
*
41 1 pfleura2
*      = U(out) * ( D(out) 0) * VT(out)
42 1 pfleura2
*
43 1 pfleura2
*  where Z' = (Z1' a Z2' b) = u' VT', and u is a vector of dimension M
44 1 pfleura2
*  with ALPHA and BETA in the NL+1 and NL+2 th entries and zeros
45 1 pfleura2
*  elsewhere; and the entry b is empty if SQRE = 0.
46 1 pfleura2
*
47 1 pfleura2
*  The singular values of B can be computed using D1, D2, the first
48 1 pfleura2
*  components of all the right singular vectors of the lower block, and
49 1 pfleura2
*  the last components of all the right singular vectors of the upper
50 1 pfleura2
*  block. These components are stored and updated in VF and VL,
51 1 pfleura2
*  respectively, in DLASD6. Hence U and VT are not explicitly
52 1 pfleura2
*  referenced.
53 1 pfleura2
*
54 1 pfleura2
*  The singular values are stored in D. The algorithm consists of two
55 1 pfleura2
*  stages:
56 1 pfleura2
*
57 1 pfleura2
*        The first stage consists of deflating the size of the problem
58 1 pfleura2
*        when there are multiple singular values or if there is a zero
59 1 pfleura2
*        in the Z vector. For each such occurence the dimension of the
60 1 pfleura2
*        secular equation problem is reduced by one. This stage is
61 1 pfleura2
*        performed by the routine DLASD7.
62 1 pfleura2
*
63 1 pfleura2
*        The second stage consists of calculating the updated
64 1 pfleura2
*        singular values. This is done by finding the roots of the
65 1 pfleura2
*        secular equation via the routine DLASD4 (as called by DLASD8).
66 1 pfleura2
*        This routine also updates VF and VL and computes the distances
67 1 pfleura2
*        between the updated singular values and the old singular
68 1 pfleura2
*        values.
69 1 pfleura2
*
70 1 pfleura2
*  DLASD6 is called from DLASDA.
71 1 pfleura2
*
72 1 pfleura2
*  Arguments
73 1 pfleura2
*  =========
74 1 pfleura2
*
75 1 pfleura2
*  ICOMPQ (input) INTEGER
76 1 pfleura2
*         Specifies whether singular vectors are to be computed in
77 1 pfleura2
*         factored form:
78 1 pfleura2
*         = 0: Compute singular values only.
79 1 pfleura2
*         = 1: Compute singular vectors in factored form as well.
80 1 pfleura2
*
81 1 pfleura2
*  NL     (input) INTEGER
82 1 pfleura2
*         The row dimension of the upper block.  NL >= 1.
83 1 pfleura2
*
84 1 pfleura2
*  NR     (input) INTEGER
85 1 pfleura2
*         The row dimension of the lower block.  NR >= 1.
86 1 pfleura2
*
87 1 pfleura2
*  SQRE   (input) INTEGER
88 1 pfleura2
*         = 0: the lower block is an NR-by-NR square matrix.
89 1 pfleura2
*         = 1: the lower block is an NR-by-(NR+1) rectangular matrix.
90 1 pfleura2
*
91 1 pfleura2
*         The bidiagonal matrix has row dimension N = NL + NR + 1,
92 1 pfleura2
*         and column dimension M = N + SQRE.
93 1 pfleura2
*
94 1 pfleura2
*  D      (input/output) DOUBLE PRECISION array, dimension ( NL+NR+1 ).
95 1 pfleura2
*         On entry D(1:NL,1:NL) contains the singular values of the
96 1 pfleura2
*         upper block, and D(NL+2:N) contains the singular values
97 1 pfleura2
*         of the lower block. On exit D(1:N) contains the singular
98 1 pfleura2
*         values of the modified matrix.
99 1 pfleura2
*
100 1 pfleura2
*  VF     (input/output) DOUBLE PRECISION array, dimension ( M )
101 1 pfleura2
*         On entry, VF(1:NL+1) contains the first components of all
102 1 pfleura2
*         right singular vectors of the upper block; and VF(NL+2:M)
103 1 pfleura2
*         contains the first components of all right singular vectors
104 1 pfleura2
*         of the lower block. On exit, VF contains the first components
105 1 pfleura2
*         of all right singular vectors of the bidiagonal matrix.
106 1 pfleura2
*
107 1 pfleura2
*  VL     (input/output) DOUBLE PRECISION array, dimension ( M )
108 1 pfleura2
*         On entry, VL(1:NL+1) contains the  last components of all
109 1 pfleura2
*         right singular vectors of the upper block; and VL(NL+2:M)
110 1 pfleura2
*         contains the last components of all right singular vectors of
111 1 pfleura2
*         the lower block. On exit, VL contains the last components of
112 1 pfleura2
*         all right singular vectors of the bidiagonal matrix.
113 1 pfleura2
*
114 1 pfleura2
*  ALPHA  (input/output) DOUBLE PRECISION
115 1 pfleura2
*         Contains the diagonal element associated with the added row.
116 1 pfleura2
*
117 1 pfleura2
*  BETA   (input/output) DOUBLE PRECISION
118 1 pfleura2
*         Contains the off-diagonal element associated with the added
119 1 pfleura2
*         row.
120 1 pfleura2
*
121 1 pfleura2
*  IDXQ   (output) INTEGER array, dimension ( N )
122 1 pfleura2
*         This contains the permutation which will reintegrate the
123 1 pfleura2
*         subproblem just solved back into sorted order, i.e.
124 1 pfleura2
*         D( IDXQ( I = 1, N ) ) will be in ascending order.
125 1 pfleura2
*
126 1 pfleura2
*  PERM   (output) INTEGER array, dimension ( N )
127 1 pfleura2
*         The permutations (from deflation and sorting) to be applied
128 1 pfleura2
*         to each block. Not referenced if ICOMPQ = 0.
129 1 pfleura2
*
130 1 pfleura2
*  GIVPTR (output) INTEGER
131 1 pfleura2
*         The number of Givens rotations which took place in this
132 1 pfleura2
*         subproblem. Not referenced if ICOMPQ = 0.
133 1 pfleura2
*
134 1 pfleura2
*  GIVCOL (output) INTEGER array, dimension ( LDGCOL, 2 )
135 1 pfleura2
*         Each pair of numbers indicates a pair of columns to take place
136 1 pfleura2
*         in a Givens rotation. Not referenced if ICOMPQ = 0.
137 1 pfleura2
*
138 1 pfleura2
*  LDGCOL (input) INTEGER
139 1 pfleura2
*         leading dimension of GIVCOL, must be at least N.
140 1 pfleura2
*
141 1 pfleura2
*  GIVNUM (output) DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
142 1 pfleura2
*         Each number indicates the C or S value to be used in the
143 1 pfleura2
*         corresponding Givens rotation. Not referenced if ICOMPQ = 0.
144 1 pfleura2
*
145 1 pfleura2
*  LDGNUM (input) INTEGER
146 1 pfleura2
*         The leading dimension of GIVNUM and POLES, must be at least N.
147 1 pfleura2
*
148 1 pfleura2
*  POLES  (output) DOUBLE PRECISION array, dimension ( LDGNUM, 2 )
149 1 pfleura2
*         On exit, POLES(1,*) is an array containing the new singular
150 1 pfleura2
*         values obtained from solving the secular equation, and
151 1 pfleura2
*         POLES(2,*) is an array containing the poles in the secular
152 1 pfleura2
*         equation. Not referenced if ICOMPQ = 0.
153 1 pfleura2
*
154 1 pfleura2
*  DIFL   (output) DOUBLE PRECISION array, dimension ( N )
155 1 pfleura2
*         On exit, DIFL(I) is the distance between I-th updated
156 1 pfleura2
*         (undeflated) singular value and the I-th (undeflated) old
157 1 pfleura2
*         singular value.
158 1 pfleura2
*
159 1 pfleura2
*  DIFR   (output) DOUBLE PRECISION array,
160 1 pfleura2
*                  dimension ( LDGNUM, 2 ) if ICOMPQ = 1 and
161 1 pfleura2
*                  dimension ( N ) if ICOMPQ = 0.
162 1 pfleura2
*         On exit, DIFR(I, 1) is the distance between I-th updated
163 1 pfleura2
*         (undeflated) singular value and the I+1-th (undeflated) old
164 1 pfleura2
*         singular value.
165 1 pfleura2
*
166 1 pfleura2
*         If ICOMPQ = 1, DIFR(1:K,2) is an array containing the
167 1 pfleura2
*         normalizing factors for the right singular vector matrix.
168 1 pfleura2
*
169 1 pfleura2
*         See DLASD8 for details on DIFL and DIFR.
170 1 pfleura2
*
171 1 pfleura2
*  Z      (output) DOUBLE PRECISION array, dimension ( M )
172 1 pfleura2
*         The first elements of this array contain the components
173 1 pfleura2
*         of the deflation-adjusted updating row vector.
174 1 pfleura2
*
175 1 pfleura2
*  K      (output) INTEGER
176 1 pfleura2
*         Contains the dimension of the non-deflated matrix,
177 1 pfleura2
*         This is the order of the related secular equation. 1 <= K <=N.
178 1 pfleura2
*
179 1 pfleura2
*  C      (output) DOUBLE PRECISION
180 1 pfleura2
*         C contains garbage if SQRE =0 and the C-value of a Givens
181 1 pfleura2
*         rotation related to the right null space if SQRE = 1.
182 1 pfleura2
*
183 1 pfleura2
*  S      (output) DOUBLE PRECISION
184 1 pfleura2
*         S contains garbage if SQRE =0 and the S-value of a Givens
185 1 pfleura2
*         rotation related to the right null space if SQRE = 1.
186 1 pfleura2
*
187 1 pfleura2
*  WORK   (workspace) DOUBLE PRECISION array, dimension ( 4 * M )
188 1 pfleura2
*
189 1 pfleura2
*  IWORK  (workspace) INTEGER array, dimension ( 3 * N )
190 1 pfleura2
*
191 1 pfleura2
*  INFO   (output) INTEGER
192 1 pfleura2
*          = 0:  successful exit.
193 1 pfleura2
*          < 0:  if INFO = -i, the i-th argument had an illegal value.
194 1 pfleura2
*          > 0:  if INFO = 1, a singular value did not converge
195 1 pfleura2
*
196 1 pfleura2
*  Further Details
197 1 pfleura2
*  ===============
198 1 pfleura2
*
199 1 pfleura2
*  Based on contributions by
200 1 pfleura2
*     Ming Gu and Huan Ren, Computer Science Division, University of
201 1 pfleura2
*     California at Berkeley, USA
202 1 pfleura2
*
203 1 pfleura2
*  =====================================================================
204 1 pfleura2
*
205 1 pfleura2
*     .. Parameters ..
206 1 pfleura2
      DOUBLE PRECISION   ONE, ZERO
207 1 pfleura2
      PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
208 1 pfleura2
*     ..
209 1 pfleura2
*     .. Local Scalars ..
210 1 pfleura2
      INTEGER            I, IDX, IDXC, IDXP, ISIGMA, IVFW, IVLW, IW, M,
211 1 pfleura2
     $                   N, N1, N2
212 1 pfleura2
      DOUBLE PRECISION   ORGNRM
213 1 pfleura2
*     ..
214 1 pfleura2
*     .. External Subroutines ..
215 1 pfleura2
      EXTERNAL           DCOPY, DLAMRG, DLASCL, DLASD7, DLASD8, XERBLA
216 1 pfleura2
*     ..
217 1 pfleura2
*     .. Intrinsic Functions ..
218 1 pfleura2
      INTRINSIC          ABS, MAX
219 1 pfleura2
*     ..
220 1 pfleura2
*     .. Executable Statements ..
221 1 pfleura2
*
222 1 pfleura2
*     Test the input parameters.
223 1 pfleura2
*
224 1 pfleura2
      INFO = 0
225 1 pfleura2
      N = NL + NR + 1
226 1 pfleura2
      M = N + SQRE
227 1 pfleura2
*
228 1 pfleura2
      IF( ( ICOMPQ.LT.0 ) .OR. ( ICOMPQ.GT.1 ) ) THEN
229 1 pfleura2
         INFO = -1
230 1 pfleura2
      ELSE IF( NL.LT.1 ) THEN
231 1 pfleura2
         INFO = -2
232 1 pfleura2
      ELSE IF( NR.LT.1 ) THEN
233 1 pfleura2
         INFO = -3
234 1 pfleura2
      ELSE IF( ( SQRE.LT.0 ) .OR. ( SQRE.GT.1 ) ) THEN
235 1 pfleura2
         INFO = -4
236 1 pfleura2
      ELSE IF( LDGCOL.LT.N ) THEN
237 1 pfleura2
         INFO = -14
238 1 pfleura2
      ELSE IF( LDGNUM.LT.N ) THEN
239 1 pfleura2
         INFO = -16
240 1 pfleura2
      END IF
241 1 pfleura2
      IF( INFO.NE.0 ) THEN
242 1 pfleura2
         CALL XERBLA( 'DLASD6', -INFO )
243 1 pfleura2
         RETURN
244 1 pfleura2
      END IF
245 1 pfleura2
*
246 1 pfleura2
*     The following values are for bookkeeping purposes only.  They are
247 1 pfleura2
*     integer pointers which indicate the portion of the workspace
248 1 pfleura2
*     used by a particular array in DLASD7 and DLASD8.
249 1 pfleura2
*
250 1 pfleura2
      ISIGMA = 1
251 1 pfleura2
      IW = ISIGMA + N
252 1 pfleura2
      IVFW = IW + M
253 1 pfleura2
      IVLW = IVFW + M
254 1 pfleura2
*
255 1 pfleura2
      IDX = 1
256 1 pfleura2
      IDXC = IDX + N
257 1 pfleura2
      IDXP = IDXC + N
258 1 pfleura2
*
259 1 pfleura2
*     Scale.
260 1 pfleura2
*
261 1 pfleura2
      ORGNRM = MAX( ABS( ALPHA ), ABS( BETA ) )
262 1 pfleura2
      D( NL+1 ) = ZERO
263 1 pfleura2
      DO 10 I = 1, N
264 1 pfleura2
         IF( ABS( D( I ) ).GT.ORGNRM ) THEN
265 1 pfleura2
            ORGNRM = ABS( D( I ) )
266 1 pfleura2
         END IF
267 1 pfleura2
   10 CONTINUE
268 1 pfleura2
      CALL DLASCL( 'G', 0, 0, ORGNRM, ONE, N, 1, D, N, INFO )
269 1 pfleura2
      ALPHA = ALPHA / ORGNRM
270 1 pfleura2
      BETA = BETA / ORGNRM
271 1 pfleura2
*
272 1 pfleura2
*     Sort and Deflate singular values.
273 1 pfleura2
*
274 1 pfleura2
      CALL DLASD7( ICOMPQ, NL, NR, SQRE, K, D, Z, WORK( IW ), VF,
275 1 pfleura2
     $             WORK( IVFW ), VL, WORK( IVLW ), ALPHA, BETA,
276 1 pfleura2
     $             WORK( ISIGMA ), IWORK( IDX ), IWORK( IDXP ), IDXQ,
277 1 pfleura2
     $             PERM, GIVPTR, GIVCOL, LDGCOL, GIVNUM, LDGNUM, C, S,
278 1 pfleura2
     $             INFO )
279 1 pfleura2
*
280 1 pfleura2
*     Solve Secular Equation, compute DIFL, DIFR, and update VF, VL.
281 1 pfleura2
*
282 1 pfleura2
      CALL DLASD8( ICOMPQ, K, D, Z, VF, VL, DIFL, DIFR, LDGNUM,
283 1 pfleura2
     $             WORK( ISIGMA ), WORK( IW ), INFO )
284 1 pfleura2
*
285 1 pfleura2
*     Save the poles if ICOMPQ = 1.
286 1 pfleura2
*
287 1 pfleura2
      IF( ICOMPQ.EQ.1 ) THEN
288 1 pfleura2
         CALL DCOPY( K, D, 1, POLES( 1, 1 ), 1 )
289 1 pfleura2
         CALL DCOPY( K, WORK( ISIGMA ), 1, POLES( 1, 2 ), 1 )
290 1 pfleura2
      END IF
291 1 pfleura2
*
292 1 pfleura2
*     Unscale.
293 1 pfleura2
*
294 1 pfleura2
      CALL DLASCL( 'G', 0, 0, ONE, ORGNRM, N, 1, D, N, INFO )
295 1 pfleura2
*
296 1 pfleura2
*     Prepare the IDXQ sorting permutation.
297 1 pfleura2
*
298 1 pfleura2
      N1 = K
299 1 pfleura2
      N2 = N - K
300 1 pfleura2
      CALL DLAMRG( N1, N2, D, 1, -1, IDXQ )
301 1 pfleura2
*
302 1 pfleura2
      RETURN
303 1 pfleura2
*
304 1 pfleura2
*     End of DLASD6
305 1 pfleura2
*
306 1 pfleura2
      END