1CGGSVP(1)                LAPACK routine (version 3.2)                CGGSVP(1)
2
3
4

NAME

6       CGGSVP  -  computes  unitary  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

SYNOPSIS

10       SUBROUTINE CGGSVP( JOBU, JOBV, JOBQ, M, P, N, A,  LDA,  B,  LDB,  TOLA,
11                          TOLB,  K,  L,  U, LDU, V, LDV, Q, LDQ, IWORK, RWORK,
12                          TAU, WORK, INFO )
13
14           CHARACTER      JOBQ, JOBU, JOBV
15
16           INTEGER        INFO, K, L, LDA, LDB, LDQ, LDU, LDV, M, N, P
17
18           REAL           TOLA, TOLB
19
20           INTEGER        IWORK( * )
21
22           REAL           RWORK( * )
23
24           COMPLEX        A( LDA, * ), B( LDB, * ), Q( LDQ, * ), TAU( * ),  U(
25                          LDU, * ), V( LDV, * ), WORK( * )
26

PURPOSE

28       CGGSVP computes unitary matrices U, V and Q such that
29                     L ( 0     0   A23 )
30                 M-K-L ( 0     0    0  )
31                        N-K-L  K    L
32               =     K ( 0    A12  A13 )  if M-K-L < 0;
33                   M-K ( 0     0   A23 )
34                      N-K-L  K    L
35        V'*B*Q =   L ( 0     0   B13 )
36                 P-L ( 0     0    0  )
37       where the K-by-K matrix A12 and L-by-L matrix B13 are nonsingular upper
38       triangular; A23 is L-by-L upper triangular if M-K-L >= 0, otherwise A23
39       is (M-K)-by-L upper trapezoidal.  K+L = the effective numerical rank of
40       the (M+P)-by-N matrix (A',B')'.  Z' denotes the conjugate transpose  of
41       Z.
42       This decomposition is the preprocessing step for computing the General‐
43       ized Singular Value Decomposition (GSVD), see subroutine CGGSVD.
44

ARGUMENTS

46       JOBU    (input) CHARACTER*1
47               = 'U':  Unitary matrix U is computed;
48               = 'N':  U is not computed.
49
50       JOBV    (input) CHARACTER*1
51               = 'V':  Unitary matrix V is computed;
52               = 'N':  V is not computed.
53
54       JOBQ    (input) CHARACTER*1
55               = 'Q':  Unitary matrix Q is computed;
56               = 'N':  Q is not computed.
57
58       M       (input) INTEGER
59               The number of rows of the matrix A.  M >= 0.
60
61       P       (input) INTEGER
62               The number of rows of the matrix B.  P >= 0.
63
64       N       (input) INTEGER
65               The number of columns of the matrices A and B.  N >= 0.
66
67       A       (input/output) COMPLEX array, dimension (LDA,N)
68               On entry, the M-by-N matrix A.  On exit, A contains the  trian‐
69               gular (or trapezoidal) matrix described in the Purpose section.
70
71       LDA     (input) INTEGER
72               The leading dimension of the array A. LDA >= max(1,M).
73
74       B       (input/output) COMPLEX array, dimension (LDB,N)
75               On  entry, the P-by-N matrix B.  On exit, B contains the trian‐
76               gular matrix described in the Purpose section.
77
78       LDB     (input) INTEGER
79               The leading dimension of the array B. LDB >= max(1,P).
80
81       TOLA    (input) REAL
82               TOLB    (input) REAL TOLA and TOLB are the thresholds to deter‐
83               mine the effective numerical rank of matrix B and a subblock of
84               A. Generally, they are set to TOLA =  MAX(M,N)*norm(A)*MACHEPS,
85               TOLB = MAX(P,N)*norm(B)*MACHEPS.  The size of TOLA and TOLB may
86               affect the size of backward errors of the decomposition.
87
88       K       (output) INTEGER
89               L       (output) INTEGER On exit, K and L specify the dimension
90               of  the subblocks described in Purpose section.  K + L = effec‐
91               tive numerical rank of (A',B')'.
92
93       U       (output) COMPLEX array, dimension (LDU,M)
94               If JOBU = 'U', U contains the unitary matrix U.  If JOBU = 'N',
95               U is not referenced.
96
97       LDU     (input) INTEGER
98               The leading dimension of the array U. LDU >= max(1,M) if JOBU =
99               'U'; LDU >= 1 otherwise.
100
101       V       (output) COMPLEX array, dimension (LDV,P)
102               If JOBV = 'V', V contains the unitary matrix V.  If JOBV = 'N',
103               V is not referenced.
104
105       LDV     (input) INTEGER
106               The leading dimension of the array V. LDV >= max(1,P) if JOBV =
107               'V'; LDV >= 1 otherwise.
108
109       Q       (output) COMPLEX array, dimension (LDQ,N)
110               If JOBQ = 'Q', Q contains the unitary matrix Q.  If JOBQ = 'N',
111               Q is not referenced.
112
113       LDQ     (input) INTEGER
114               The leading dimension of the array Q. LDQ >= max(1,N) if JOBQ =
115               'Q'; LDQ >= 1 otherwise.
116
117       IWORK   (workspace) INTEGER array, dimension (N)
118
119       RWORK   (workspace) REAL array, dimension (2*N)
120
121       TAU     (workspace) COMPLEX array, dimension (N)
122
123       WORK    (workspace) COMPLEX array, dimension (max(3*N,M,P))
124
125       INFO    (output) INTEGER
126               = 0:  successful exit
127               < 0:  if INFO = -i, the i-th argument had an illegal value.
128

FURTHER DETAILS

130       The subroutine uses LAPACK subroutine CGEQPF for the  QR  factorization
131       with  column  pivoting  to detect the effective numerical rank of the a
132       matrix. It may be replaced by a better rank determination strategy.
133
134
135
136 LAPACK routine (version 3.2)    November 2008                       CGGSVP(1)
Impressum