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