1DGGSVP(1) LAPACK routine (version 3.2) DGGSVP(1)
2
3
4
6 DGGSVP - computes orthogonal matrices U, V and Q such that N-K-L K L
7 U'*A*Q = K ( 0 A12 A13 ) if M-K-L >= 0
8
10 SUBROUTINE DGGSVP( JOBU, JOBV, JOBQ, M, P, N, A, LDA, B, LDB, TOLA,
11 TOLB, K, L, U, LDU, V, LDV, Q, LDQ, IWORK, TAU,
12 WORK, INFO )
13
14 CHARACTER JOBQ, JOBU, JOBV
15
16 INTEGER INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, P
17
18 DOUBLE PRECISION TOLA, TOLB
19
20 INTEGER IWORK( * )
21
22 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
23 TAU( * ), U( LDU, * ), V( LDV, * ), WORK( * )
24
26 DGGSVP computes orthogonal matrices U, V and Q such that
27 L ( 0 0 A23 )
28 M-K-L ( 0 0 0 )
29 N-K-L K L
30 = K ( 0 A12 A13 ) if M-K-L < 0;
31 M-K ( 0 0 A23 )
32 N-K-L K L
33 V'*B*Q = L ( 0 0 B13 )
34 P-L ( 0 0 0 )
35 where the K-by-K matrix A12 and L-by-L matrix B13 are nonsingular upper
36 triangular; A23 is L-by-L upper triangular if M-K-L >= 0, otherwise A23
37 is (M-K)-by-L upper trapezoidal. K+L = the effective numerical rank of
38 the (M+P)-by-N matrix (A',B')'. Z' denotes the transpose of Z.
39 This decomposition is the preprocessing step for computing the General‐
40 ized Singular Value Decomposition (GSVD), see subroutine DGGSVD.
41
43 JOBU (input) CHARACTER*1
44 = 'U': Orthogonal matrix U is computed;
45 = 'N': U is not computed.
46
47 JOBV (input) CHARACTER*1
48 = 'V': Orthogonal matrix V is computed;
49 = 'N': V is not computed.
50
51 JOBQ (input) CHARACTER*1
52 = 'Q': Orthogonal matrix Q is computed;
53 = 'N': Q is not computed.
54
55 M (input) INTEGER
56 The number of rows of the matrix A. M >= 0.
57
58 P (input) INTEGER
59 The number of rows of the matrix B. P >= 0.
60
61 N (input) INTEGER
62 The number of columns of the matrices A and B. N >= 0.
63
64 A (input/output) DOUBLE PRECISION array, dimension (LDA,N)
65 On entry, the M-by-N matrix A. On exit, A contains the trian‐
66 gular (or trapezoidal) matrix described in the Purpose section.
67
68 LDA (input) INTEGER
69 The leading dimension of the array A. LDA >= max(1,M).
70
71 B (input/output) DOUBLE PRECISION array, dimension (LDB,N)
72 On entry, the P-by-N matrix B. On exit, B contains the trian‐
73 gular matrix described in the Purpose section.
74
75 LDB (input) INTEGER
76 The leading dimension of the array B. LDB >= max(1,P).
77
78 TOLA (input) DOUBLE PRECISION
79 TOLB (input) DOUBLE PRECISION TOLA and TOLB are the thresh‐
80 olds to determine the effective numerical rank of matrix B and
81 a subblock of A. Generally, they are set to TOLA =
82 MAX(M,N)*norm(A)*MAZHEPS, TOLB = MAX(P,N)*norm(B)*MAZHEPS. The
83 size of TOLA and TOLB may affect the size of backward errors of
84 the decomposition.
85
86 K (output) INTEGER
87 L (output) INTEGER On exit, K and L specify the dimension
88 of the subblocks described in Purpose. K + L = effective
89 numerical rank of (A',B')'.
90
91 U (output) DOUBLE PRECISION array, dimension (LDU,M)
92 If JOBU = 'U', U contains the orthogonal matrix U. If JOBU =
93 'N', U is not referenced.
94
95 LDU (input) INTEGER
96 The leading dimension of the array U. LDU >= max(1,M) if JOBU =
97 'U'; LDU >= 1 otherwise.
98
99 V (output) DOUBLE PRECISION array, dimension (LDV,P)
100 If JOBV = 'V', V contains the orthogonal matrix V. If JOBV =
101 'N', V is not referenced.
102
103 LDV (input) INTEGER
104 The leading dimension of the array V. LDV >= max(1,P) if JOBV =
105 'V'; LDV >= 1 otherwise.
106
107 Q (output) DOUBLE PRECISION array, dimension (LDQ,N)
108 If JOBQ = 'Q', Q contains the orthogonal matrix Q. If JOBQ =
109 'N', Q is not referenced.
110
111 LDQ (input) INTEGER
112 The leading dimension of the array Q. LDQ >= max(1,N) if JOBQ =
113 'Q'; LDQ >= 1 otherwise.
114
115 IWORK (workspace) INTEGER array, dimension (N)
116
117 TAU (workspace) DOUBLE PRECISION array, dimension (N)
118
119 WORK (workspace) DOUBLE PRECISION array, dimension (max(3*N,M,P))
120
121 INFO (output) INTEGER
122 = 0: successful exit
123 < 0: if INFO = -i, the i-th argument had an illegal value.
124
126 The subroutine uses LAPACK subroutine DGEQPF for the QR factorization
127 with column pivoting to detect the effective numerical rank of the a
128 matrix. It may be replaced by a better rank determination strategy.
129
130
131
132 LAPACK routine (version 3.2) November 2008 DGGSVP(1)