LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sggsvp.f
Go to the documentation of this file.
1 *> \brief \b SGGSVP
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SGGSVP + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sggsvp.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sggsvp.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sggsvp.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SGGSVP( JOBU, JOBV, JOBQ, M, P, N, A, LDA, B, LDB,
22 * TOLA, TOLB, K, L, U, LDU, V, LDV, Q, LDQ,
23 * IWORK, TAU, WORK, INFO )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER JOBQ, JOBU, JOBV
27 * INTEGER INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, P
28 * REAL TOLA, TOLB
29 * ..
30 * .. Array Arguments ..
31 * INTEGER IWORK( * )
32 * REAL A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
33 * $ TAU( * ), U( LDU, * ), V( LDV, * ), WORK( * )
34 * ..
35 *
36 *
37 *> \par Purpose:
38 * =============
39 *>
40 *> \verbatim
41 *>
42 *> This routine is deprecated and has been replaced by routine SGGSVP3.
43 *>
44 *> SGGSVP computes orthogonal matrices U, V and Q such that
45 *>
46 *> N-K-L K L
47 *> U**T*A*Q = K ( 0 A12 A13 ) if M-K-L >= 0;
48 *> L ( 0 0 A23 )
49 *> M-K-L ( 0 0 0 )
50 *>
51 *> N-K-L K L
52 *> = K ( 0 A12 A13 ) if M-K-L < 0;
53 *> M-K ( 0 0 A23 )
54 *>
55 *> N-K-L K L
56 *> V**T*B*Q = L ( 0 0 B13 )
57 *> P-L ( 0 0 0 )
58 *>
59 *> where the K-by-K matrix A12 and L-by-L matrix B13 are nonsingular
60 *> upper triangular; A23 is L-by-L upper triangular if M-K-L >= 0,
61 *> otherwise A23 is (M-K)-by-L upper trapezoidal. K+L = the effective
62 *> numerical rank of the (M+P)-by-N matrix (A**T,B**T)**T.
63 *>
64 *> This decomposition is the preprocessing step for computing the
65 *> Generalized Singular Value Decomposition (GSVD), see subroutine
66 *> SGGSVD.
67 *> \endverbatim
68 *
69 * Arguments:
70 * ==========
71 *
72 *> \param[in] JOBU
73 *> \verbatim
74 *> JOBU is CHARACTER*1
75 *> = 'U': Orthogonal matrix U is computed;
76 *> = 'N': U is not computed.
77 *> \endverbatim
78 *>
79 *> \param[in] JOBV
80 *> \verbatim
81 *> JOBV is CHARACTER*1
82 *> = 'V': Orthogonal matrix V is computed;
83 *> = 'N': V is not computed.
84 *> \endverbatim
85 *>
86 *> \param[in] JOBQ
87 *> \verbatim
88 *> JOBQ is CHARACTER*1
89 *> = 'Q': Orthogonal matrix Q is computed;
90 *> = 'N': Q is not computed.
91 *> \endverbatim
92 *>
93 *> \param[in] M
94 *> \verbatim
95 *> M is INTEGER
96 *> The number of rows of the matrix A. M >= 0.
97 *> \endverbatim
98 *>
99 *> \param[in] P
100 *> \verbatim
101 *> P is INTEGER
102 *> The number of rows of the matrix B. P >= 0.
103 *> \endverbatim
104 *>
105 *> \param[in] N
106 *> \verbatim
107 *> N is INTEGER
108 *> The number of columns of the matrices A and B. N >= 0.
109 *> \endverbatim
110 *>
111 *> \param[in,out] A
112 *> \verbatim
113 *> A is REAL array, dimension (LDA,N)
114 *> On entry, the M-by-N matrix A.
115 *> On exit, A contains the triangular (or trapezoidal) matrix
116 *> described in the Purpose section.
117 *> \endverbatim
118 *>
119 *> \param[in] LDA
120 *> \verbatim
121 *> LDA is INTEGER
122 *> The leading dimension of the array A. LDA >= max(1,M).
123 *> \endverbatim
124 *>
125 *> \param[in,out] B
126 *> \verbatim
127 *> B is REAL array, dimension (LDB,N)
128 *> On entry, the P-by-N matrix B.
129 *> On exit, B contains the triangular matrix described in
130 *> the Purpose section.
131 *> \endverbatim
132 *>
133 *> \param[in] LDB
134 *> \verbatim
135 *> LDB is INTEGER
136 *> The leading dimension of the array B. LDB >= max(1,P).
137 *> \endverbatim
138 *>
139 *> \param[in] TOLA
140 *> \verbatim
141 *> TOLA is REAL
142 *> \endverbatim
143 *>
144 *> \param[in] TOLB
145 *> \verbatim
146 *> TOLB is REAL
147 *>
148 *> TOLA and TOLB are the thresholds to determine the effective
149 *> numerical rank of matrix B and a subblock of A. Generally,
150 *> they are set to
151 *> TOLA = MAX(M,N)*norm(A)*MACHEPS,
152 *> TOLB = MAX(P,N)*norm(B)*MACHEPS.
153 *> The size of TOLA and TOLB may affect the size of backward
154 *> errors of the decomposition.
155 *> \endverbatim
156 *>
157 *> \param[out] K
158 *> \verbatim
159 *> K is INTEGER
160 *> \endverbatim
161 *>
162 *> \param[out] L
163 *> \verbatim
164 *> L is INTEGER
165 *>
166 *> On exit, K and L specify the dimension of the subblocks
167 *> described in Purpose section.
168 *> K + L = effective numerical rank of (A**T,B**T)**T.
169 *> \endverbatim
170 *>
171 *> \param[out] U
172 *> \verbatim
173 *> U is REAL array, dimension (LDU,M)
174 *> If JOBU = 'U', U contains the orthogonal matrix U.
175 *> If JOBU = 'N', U is not referenced.
176 *> \endverbatim
177 *>
178 *> \param[in] LDU
179 *> \verbatim
180 *> LDU is INTEGER
181 *> The leading dimension of the array U. LDU >= max(1,M) if
182 *> JOBU = 'U'; LDU >= 1 otherwise.
183 *> \endverbatim
184 *>
185 *> \param[out] V
186 *> \verbatim
187 *> V is REAL array, dimension (LDV,P)
188 *> If JOBV = 'V', V contains the orthogonal matrix V.
189 *> If JOBV = 'N', V is not referenced.
190 *> \endverbatim
191 *>
192 *> \param[in] LDV
193 *> \verbatim
194 *> LDV is INTEGER
195 *> The leading dimension of the array V. LDV >= max(1,P) if
196 *> JOBV = 'V'; LDV >= 1 otherwise.
197 *> \endverbatim
198 *>
199 *> \param[out] Q
200 *> \verbatim
201 *> Q is REAL array, dimension (LDQ,N)
202 *> If JOBQ = 'Q', Q contains the orthogonal matrix Q.
203 *> If JOBQ = 'N', Q is not referenced.
204 *> \endverbatim
205 *>
206 *> \param[in] LDQ
207 *> \verbatim
208 *> LDQ is INTEGER
209 *> The leading dimension of the array Q. LDQ >= max(1,N) if
210 *> JOBQ = 'Q'; LDQ >= 1 otherwise.
211 *> \endverbatim
212 *>
213 *> \param[out] IWORK
214 *> \verbatim
215 *> IWORK is INTEGER array, dimension (N)
216 *> \endverbatim
217 *>
218 *> \param[out] TAU
219 *> \verbatim
220 *> TAU is REAL array, dimension (N)
221 *> \endverbatim
222 *>
223 *> \param[out] WORK
224 *> \verbatim
225 *> WORK is REAL array, dimension (max(3*N,M,P))
226 *> \endverbatim
227 *>
228 *> \param[out] INFO
229 *> \verbatim
230 *> INFO is INTEGER
231 *> = 0: successful exit
232 *> < 0: if INFO = -i, the i-th argument had an illegal value.
233 *> \endverbatim
234 *
235 * Authors:
236 * ========
237 *
238 *> \author Univ. of Tennessee
239 *> \author Univ. of California Berkeley
240 *> \author Univ. of Colorado Denver
241 *> \author NAG Ltd.
242 *
243 *> \date November 2011
244 *
245 *> \ingroup realOTHERcomputational
246 *
247 *> \par Further Details:
248 * =====================
249 *>
250 *> The subroutine uses LAPACK subroutine SGEQPF for the QR factorization
251 *> with column pivoting to detect the effective numerical rank of the
252 *> a matrix. It may be replaced by a better rank determination strategy.
253 *>
254 * =====================================================================
255  SUBROUTINE sggsvp( JOBU, JOBV, JOBQ, M, P, N, A, LDA, B, LDB,
256  $ tola, tolb, k, l, u, ldu, v, ldv, q, ldq,
257  $ iwork, tau, work, info )
258 *
259 * -- LAPACK computational routine (version 3.4.0) --
260 * -- LAPACK is a software package provided by Univ. of Tennessee, --
261 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
262 * November 2011
263 *
264 * .. Scalar Arguments ..
265  CHARACTER JOBQ, JOBU, JOBV
266  INTEGER INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, P
267  REAL TOLA, TOLB
268 * ..
269 * .. Array Arguments ..
270  INTEGER IWORK( * )
271  REAL A( lda, * ), B( ldb, * ), Q( ldq, * ),
272  $ tau( * ), u( ldu, * ), v( ldv, * ), work( * )
273 * ..
274 *
275 * =====================================================================
276 *
277 * .. Parameters ..
278  REAL ZERO, ONE
279  parameter ( zero = 0.0e+0, one = 1.0e+0 )
280 * ..
281 * .. Local Scalars ..
282  LOGICAL FORWRD, WANTQ, WANTU, WANTV
283  INTEGER I, J
284 * ..
285 * .. External Functions ..
286  LOGICAL LSAME
287  EXTERNAL lsame
288 * ..
289 * .. External Subroutines ..
290  EXTERNAL sgeqpf, sgeqr2, sgerq2, slacpy, slapmt, slaset,
292 * ..
293 * .. Intrinsic Functions ..
294  INTRINSIC abs, max, min
295 * ..
296 * .. Executable Statements ..
297 *
298 * Test the input parameters
299 *
300  wantu = lsame( jobu, 'U' )
301  wantv = lsame( jobv, 'V' )
302  wantq = lsame( jobq, 'Q' )
303  forwrd = .true.
304 *
305  info = 0
306  IF( .NOT.( wantu .OR. lsame( jobu, 'N' ) ) ) THEN
307  info = -1
308  ELSE IF( .NOT.( wantv .OR. lsame( jobv, 'N' ) ) ) THEN
309  info = -2
310  ELSE IF( .NOT.( wantq .OR. lsame( jobq, 'N' ) ) ) THEN
311  info = -3
312  ELSE IF( m.LT.0 ) THEN
313  info = -4
314  ELSE IF( p.LT.0 ) THEN
315  info = -5
316  ELSE IF( n.LT.0 ) THEN
317  info = -6
318  ELSE IF( lda.LT.max( 1, m ) ) THEN
319  info = -8
320  ELSE IF( ldb.LT.max( 1, p ) ) THEN
321  info = -10
322  ELSE IF( ldu.LT.1 .OR. ( wantu .AND. ldu.LT.m ) ) THEN
323  info = -16
324  ELSE IF( ldv.LT.1 .OR. ( wantv .AND. ldv.LT.p ) ) THEN
325  info = -18
326  ELSE IF( ldq.LT.1 .OR. ( wantq .AND. ldq.LT.n ) ) THEN
327  info = -20
328  END IF
329  IF( info.NE.0 ) THEN
330  CALL xerbla( 'SGGSVP', -info )
331  RETURN
332  END IF
333 *
334 * QR with column pivoting of B: B*P = V*( S11 S12 )
335 * ( 0 0 )
336 *
337  DO 10 i = 1, n
338  iwork( i ) = 0
339  10 CONTINUE
340  CALL sgeqpf( p, n, b, ldb, iwork, tau, work, info )
341 *
342 * Update A := A*P
343 *
344  CALL slapmt( forwrd, m, n, a, lda, iwork )
345 *
346 * Determine the effective rank of matrix B.
347 *
348  l = 0
349  DO 20 i = 1, min( p, n )
350  IF( abs( b( i, i ) ).GT.tolb )
351  $ l = l + 1
352  20 CONTINUE
353 *
354  IF( wantv ) THEN
355 *
356 * Copy the details of V, and form V.
357 *
358  CALL slaset( 'Full', p, p, zero, zero, v, ldv )
359  IF( p.GT.1 )
360  $ CALL slacpy( 'Lower', p-1, n, b( 2, 1 ), ldb, v( 2, 1 ),
361  $ ldv )
362  CALL sorg2r( p, p, min( p, n ), v, ldv, tau, work, info )
363  END IF
364 *
365 * Clean up B
366 *
367  DO 40 j = 1, l - 1
368  DO 30 i = j + 1, l
369  b( i, j ) = zero
370  30 CONTINUE
371  40 CONTINUE
372  IF( p.GT.l )
373  $ CALL slaset( 'Full', p-l, n, zero, zero, b( l+1, 1 ), ldb )
374 *
375  IF( wantq ) THEN
376 *
377 * Set Q = I and Update Q := Q*P
378 *
379  CALL slaset( 'Full', n, n, zero, one, q, ldq )
380  CALL slapmt( forwrd, n, n, q, ldq, iwork )
381  END IF
382 *
383  IF( p.GE.l .AND. n.NE.l ) THEN
384 *
385 * RQ factorization of (S11 S12): ( S11 S12 ) = ( 0 S12 )*Z
386 *
387  CALL sgerq2( l, n, b, ldb, tau, work, info )
388 *
389 * Update A := A*Z**T
390 *
391  CALL sormr2( 'Right', 'Transpose', m, n, l, b, ldb, tau, a,
392  $ lda, work, info )
393 *
394  IF( wantq ) THEN
395 *
396 * Update Q := Q*Z**T
397 *
398  CALL sormr2( 'Right', 'Transpose', n, n, l, b, ldb, tau, q,
399  $ ldq, work, info )
400  END IF
401 *
402 * Clean up B
403 *
404  CALL slaset( 'Full', l, n-l, zero, zero, b, ldb )
405  DO 60 j = n - l + 1, n
406  DO 50 i = j - n + l + 1, l
407  b( i, j ) = zero
408  50 CONTINUE
409  60 CONTINUE
410 *
411  END IF
412 *
413 * Let N-L L
414 * A = ( A11 A12 ) M,
415 *
416 * then the following does the complete QR decomposition of A11:
417 *
418 * A11 = U*( 0 T12 )*P1**T
419 * ( 0 0 )
420 *
421  DO 70 i = 1, n - l
422  iwork( i ) = 0
423  70 CONTINUE
424  CALL sgeqpf( m, n-l, a, lda, iwork, tau, work, info )
425 *
426 * Determine the effective rank of A11
427 *
428  k = 0
429  DO 80 i = 1, min( m, n-l )
430  IF( abs( a( i, i ) ).GT.tola )
431  $ k = k + 1
432  80 CONTINUE
433 *
434 * Update A12 := U**T*A12, where A12 = A( 1:M, N-L+1:N )
435 *
436  CALL sorm2r( 'Left', 'Transpose', m, l, min( m, n-l ), a, lda,
437  $ tau, a( 1, n-l+1 ), lda, work, info )
438 *
439  IF( wantu ) THEN
440 *
441 * Copy the details of U, and form U
442 *
443  CALL slaset( 'Full', m, m, zero, zero, u, ldu )
444  IF( m.GT.1 )
445  $ CALL slacpy( 'Lower', m-1, n-l, a( 2, 1 ), lda, u( 2, 1 ),
446  $ ldu )
447  CALL sorg2r( m, m, min( m, n-l ), u, ldu, tau, work, info )
448  END IF
449 *
450  IF( wantq ) THEN
451 *
452 * Update Q( 1:N, 1:N-L ) = Q( 1:N, 1:N-L )*P1
453 *
454  CALL slapmt( forwrd, n, n-l, q, ldq, iwork )
455  END IF
456 *
457 * Clean up A: set the strictly lower triangular part of
458 * A(1:K, 1:K) = 0, and A( K+1:M, 1:N-L ) = 0.
459 *
460  DO 100 j = 1, k - 1
461  DO 90 i = j + 1, k
462  a( i, j ) = zero
463  90 CONTINUE
464  100 CONTINUE
465  IF( m.GT.k )
466  $ CALL slaset( 'Full', m-k, n-l, zero, zero, a( k+1, 1 ), lda )
467 *
468  IF( n-l.GT.k ) THEN
469 *
470 * RQ factorization of ( T11 T12 ) = ( 0 T12 )*Z1
471 *
472  CALL sgerq2( k, n-l, a, lda, tau, work, info )
473 *
474  IF( wantq ) THEN
475 *
476 * Update Q( 1:N,1:N-L ) = Q( 1:N,1:N-L )*Z1**T
477 *
478  CALL sormr2( 'Right', 'Transpose', n, n-l, k, a, lda, tau,
479  $ q, ldq, work, info )
480  END IF
481 *
482 * Clean up A
483 *
484  CALL slaset( 'Full', k, n-l-k, zero, zero, a, lda )
485  DO 120 j = n - l - k + 1, n - l
486  DO 110 i = j - n + l + k + 1, k
487  a( i, j ) = zero
488  110 CONTINUE
489  120 CONTINUE
490 *
491  END IF
492 *
493  IF( m.GT.k ) THEN
494 *
495 * QR factorization of A( K+1:M,N-L+1:N )
496 *
497  CALL sgeqr2( m-k, l, a( k+1, n-l+1 ), lda, tau, work, info )
498 *
499  IF( wantu ) THEN
500 *
501 * Update U(:,K+1:M) := U(:,K+1:M)*U1
502 *
503  CALL sorm2r( 'Right', 'No transpose', m, m-k, min( m-k, l ),
504  $ a( k+1, n-l+1 ), lda, tau, u( 1, k+1 ), ldu,
505  $ work, info )
506  END IF
507 *
508 * Clean up
509 *
510  DO 140 j = n - l + 1, n
511  DO 130 i = j - n + k + l + 1, m
512  a( i, j ) = zero
513  130 CONTINUE
514  140 CONTINUE
515 *
516  END IF
517 *
518  RETURN
519 *
520 * End of SGGSVP
521 *
522  END
subroutine slapmt(FORWRD, M, N, X, LDX, K)
SLAPMT performs a forward or backward permutation of the columns of a matrix.
Definition: slapmt.f:106
subroutine sgeqpf(M, N, A, LDA, JPVT, TAU, WORK, INFO)
SGEQPF
Definition: sgeqpf.f:144
subroutine sggsvp(JOBU, JOBV, JOBQ, M, P, N, A, LDA, B, LDB, TOLA, TOLB, K, L, U, LDU, V, LDV, Q, LDQ, IWORK, TAU, WORK, INFO)
SGGSVP
Definition: sggsvp.f:258
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine slacpy(UPLO, M, N, A, LDA, B, LDB)
SLACPY copies all or part of one two-dimensional array to another.
Definition: slacpy.f:105
subroutine sgeqr2(M, N, A, LDA, TAU, WORK, INFO)
SGEQR2 computes the QR factorization of a general rectangular matrix using an unblocked algorithm...
Definition: sgeqr2.f:123
subroutine slaset(UPLO, M, N, ALPHA, BETA, A, LDA)
SLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: slaset.f:112
subroutine sorg2r(M, N, K, A, LDA, TAU, WORK, INFO)
SORG2R generates all or part of the orthogonal matrix Q from a QR factorization determined by sgeqrf ...
Definition: sorg2r.f:116
subroutine sorm2r(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO)
SORM2R multiplies a general matrix by the orthogonal matrix from a QR factorization determined by sge...
Definition: sorm2r.f:161
subroutine sgerq2(M, N, A, LDA, TAU, WORK, INFO)
SGERQ2 computes the RQ factorization of a general rectangular matrix using an unblocked algorithm...
Definition: sgerq2.f:125
subroutine sormr2(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, INFO)
SORMR2 multiplies a general matrix by the orthogonal matrix from a RQ factorization determined by sge...
Definition: sormr2.f:161