1ZUNMBR(1) LAPACK routine (version 3.1) ZUNMBR(1)
2
3
4
6 ZUNMBR - = 'Q', ZUNMBR overwrites the general complex M-by-N matrix C
7 with SIDE = 'L' SIDE = 'R' TRANS = 'N'
8
10 SUBROUTINE ZUNMBR( VECT, SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC,
11 WORK, LWORK, INFO )
12
13 CHARACTER SIDE, TRANS, VECT
14
15 INTEGER INFO, K, LDA, LDC, LWORK, M, N
16
17 COMPLEX*16 A( LDA, * ), C( LDC, * ), TAU( * ), WORK( * )
18
20 If VECT = 'Q', ZUNMBR overwrites the general complex M-by-N matrix C
21 with
22 SIDE = 'L' SIDE = 'R' TRANS = 'N': Q * C
23 C * Q TRANS = 'C': Q**H * C C * Q**H
24
25 If VECT = 'P', ZUNMBR overwrites the general complex M-by-N matrix C
26 with
27 SIDE = 'L' SIDE = 'R'
28 TRANS = 'N': P * C C * P
29 TRANS = 'C': P**H * C C * P**H
30
31 Here Q and P**H are the unitary matrices determined by ZGEBRD when
32 reducing a complex matrix A to bidiagonal form: A = Q * B * P**H. Q and
33 P**H are defined as products of elementary reflectors H(i) and G(i)
34 respectively.
35
36 Let nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Thus nq is the order
37 of the unitary matrix Q or P**H that is applied.
38
39 If VECT = 'Q', A is assumed to have been an NQ-by-K matrix: if nq >= k,
40 Q = H(1) H(2) . . . H(k);
41 if nq < k, Q = H(1) H(2) . . . H(nq-1).
42
43 If VECT = 'P', A is assumed to have been a K-by-NQ matrix: if k < nq, P
44 = G(1) G(2) . . . G(k);
45 if k >= nq, P = G(1) G(2) . . . G(nq-1).
46
47
49 VECT (input) CHARACTER*1
50 = 'Q': apply Q or Q**H;
51 = 'P': apply P or P**H.
52
53 SIDE (input) CHARACTER*1
54 = 'L': apply Q, Q**H, P or P**H from the Left;
55 = 'R': apply Q, Q**H, P or P**H from the Right.
56
57 TRANS (input) CHARACTER*1
58 = 'N': No transpose, apply Q or P;
59 = 'C': Conjugate transpose, apply Q**H or P**H.
60
61 M (input) INTEGER
62 The number of rows of the matrix C. M >= 0.
63
64 N (input) INTEGER
65 The number of columns of the matrix C. N >= 0.
66
67 K (input) INTEGER
68 If VECT = 'Q', the number of columns in the original matrix
69 reduced by ZGEBRD. If VECT = 'P', the number of rows in the
70 original matrix reduced by ZGEBRD. K >= 0.
71
72 A (input) COMPLEX*16 array, dimension
73 (LDA,min(nq,K)) if VECT = 'Q' (LDA,nq) if VECT = 'P' The
74 vectors which define the elementary reflectors H(i) and G(i),
75 whose products determine the matrices Q and P, as returned by
76 ZGEBRD.
77
78 LDA (input) INTEGER
79 The leading dimension of the array A. If VECT = 'Q', LDA >=
80 max(1,nq); if VECT = 'P', LDA >= max(1,min(nq,K)).
81
82 TAU (input) COMPLEX*16 array, dimension (min(nq,K))
83 TAU(i) must contain the scalar factor of the elementary reflecā
84 tor H(i) or G(i) which determines Q or P, as returned by ZGEBRD
85 in the array argument TAUQ or TAUP.
86
87 C (input/output) COMPLEX*16 array, dimension (LDC,N)
88 On entry, the M-by-N matrix C. On exit, C is overwritten by
89 Q*C or Q**H*C or C*Q**H or C*Q or P*C or P**H*C or C*P or
90 C*P**H.
91
92 LDC (input) INTEGER
93 The leading dimension of the array C. LDC >= max(1,M).
94
95 WORK (workspace/output) COMPLEX*16 array, dimension (MAX(1,LWORK))
96 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
97
98 LWORK (input) INTEGER
99 The dimension of the array WORK. If SIDE = 'L', LWORK >=
100 max(1,N); if SIDE = 'R', LWORK >= max(1,M); if N = 0 or M = 0,
101 LWORK >= 1. For optimum performance LWORK >= max(1,N*NB) if
102 SIDE = 'L', and LWORK >= max(1,M*NB) if SIDE = 'R', where NB is
103 the optimal blocksize. (NB = 0 if M = 0 or N = 0.)
104
105 If LWORK = -1, then a workspace query is assumed; the routine
106 only calculates the optimal size of the WORK array, returns
107 this value as the first entry of the WORK array, and no error
108 message related to LWORK is issued by XERBLA.
109
110 INFO (output) INTEGER
111 = 0: successful exit
112 < 0: if INFO = -i, the i-th argument had an illegal value
113
114
115
116 LAPACK routine (version 3.1) November 2006 ZUNMBR(1)