LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
cgelqt.f
Go to the documentation of this file.
1 *> \brief \b CGELQT
2 *
3 * Definition:
4 * ===========
5 *
6 * SUBROUTINE CGELQT( M, N, MB, A, LDA, T, LDT, WORK, INFO )
7 *
8 * .. Scalar Arguments ..
9 * INTEGER INFO, LDA, LDT, M, N, MB
10 * ..
11 * .. Array Arguments ..
12 * COMPLEX A( LDA, * ), T( LDT, * ), WORK( * )
13 * ..
14 *
15 *
16 *> \par Purpose:
17 * =============
18 *>
19 *> \verbatim
20 *>
21 *> CGELQT computes a blocked LQ factorization of a complex M-by-N matrix A
22 *> using the compact WY representation of Q.
23 *> \endverbatim
24 *
25 * Arguments:
26 * ==========
27 *
28 *> \param[in] M
29 *> \verbatim
30 *> M is INTEGER
31 *> The number of rows of the matrix A. M >= 0.
32 *> \endverbatim
33 *>
34 *> \param[in] N
35 *> \verbatim
36 *> N is INTEGER
37 *> The number of columns of the matrix A. N >= 0.
38 *> \endverbatim
39 *>
40 *> \param[in] MB
41 *> \verbatim
42 *> MB is INTEGER
43 *> The block size to be used in the blocked QR. MIN(M,N) >= MB >= 1.
44 *> \endverbatim
45 *>
46 *> \param[in,out] A
47 *> \verbatim
48 *> A is COMPLEX array, dimension (LDA,N)
49 *> On entry, the M-by-N matrix A.
50 *> On exit, the elements on and below the diagonal of the array
51 *> contain the M-by-MIN(M,N) lower trapezoidal matrix L (L is
52 *> lower triangular if M <= N); the elements above the diagonal
53 *> are the rows of V.
54 *> \endverbatim
55 *>
56 *> \param[in] LDA
57 *> \verbatim
58 *> LDA is INTEGER
59 *> The leading dimension of the array A. LDA >= max(1,M).
60 *> \endverbatim
61 *>
62 *> \param[out] T
63 *> \verbatim
64 *> T is COMPLEX array, dimension (LDT,MIN(M,N))
65 *> The upper triangular block reflectors stored in compact form
66 *> as a sequence of upper triangular blocks. See below
67 *> for further details.
68 *> \endverbatim
69 *>
70 *> \param[in] LDT
71 *> \verbatim
72 *> LDT is INTEGER
73 *> The leading dimension of the array T. LDT >= MB.
74 *> \endverbatim
75 *>
76 *> \param[out] WORK
77 *> \verbatim
78 *> WORK is COMPLEX array, dimension (MB*N)
79 *> \endverbatim
80 *>
81 *> \param[out] INFO
82 *> \verbatim
83 *> INFO is INTEGER
84 *> = 0: successful exit
85 *> < 0: if INFO = -i, the i-th argument had an illegal value
86 *> \endverbatim
87 *
88 * Authors:
89 * ========
90 *
91 *> \author Univ. of Tennessee
92 *> \author Univ. of California Berkeley
93 *> \author Univ. of Colorado Denver
94 *> \author NAG Ltd.
95 *
96 *> \date June 2017
97 *
98 *> \ingroup doubleGEcomputational
99 *
100 *> \par Further Details:
101 * =====================
102 *>
103 *> \verbatim
104 *>
105 *> The matrix V stores the elementary reflectors H(i) in the i-th row
106 *> above the diagonal. For example, if M=5 and N=3, the matrix V is
107 *>
108 *> V = ( 1 v1 v1 v1 v1 )
109 *> ( 1 v2 v2 v2 )
110 *> ( 1 v3 v3 )
111 *>
112 *>
113 *> where the vi's represent the vectors which define H(i), which are returned
114 *> in the matrix A. The 1's along the diagonal of V are not stored in A.
115 *> Let K=MIN(M,N). The number of blocks is B = ceiling(K/MB), where each
116 *> block is of order MB except for the last block, which is of order
117 *> IB = K - (B-1)*MB. For each of the B blocks, a upper triangular block
118 *> reflector factor is computed: T1, T2, ..., TB. The MB-by-MB (and IB-by-IB
119 *> for the last block) T's are stored in the MB-by-K matrix T as
120 *>
121 *> T = (T1 T2 ... TB).
122 *> \endverbatim
123 *>
124 * =====================================================================
125  SUBROUTINE cgelqt( M, N, MB, A, LDA, T, LDT, WORK, INFO )
126 *
127 * -- LAPACK computational routine (version 3.7.1) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * June 2017
131 *
132 * .. Scalar Arguments ..
133  INTEGER INFO, LDA, LDT, M, N, MB
134 * ..
135 * .. Array Arguments ..
136  COMPLEX A( LDA, * ), T( LDT, * ), WORK( * )
137 * ..
138 *
139 * =====================================================================
140 *
141 * ..
142 * .. Local Scalars ..
143  INTEGER I, IB, IINFO, K
144 * ..
145 * .. External Subroutines ..
146  EXTERNAL cgelqt3, clarfb, xerbla
147 * ..
148 * .. Executable Statements ..
149 *
150 * Test the input arguments
151 *
152  info = 0
153  IF( m.LT.0 ) THEN
154  info = -1
155  ELSE IF( n.LT.0 ) THEN
156  info = -2
157  ELSE IF( mb.LT.1 .OR. (mb.GT.min(m,n) .AND. min(m,n).GT.0 ))THEN
158  info = -3
159  ELSE IF( lda.LT.max( 1, m ) ) THEN
160  info = -5
161  ELSE IF( ldt.LT.mb ) THEN
162  info = -7
163  END IF
164  IF( info.NE.0 ) THEN
165  CALL xerbla( 'CGELQT', -info )
166  RETURN
167  END IF
168 *
169 * Quick return if possible
170 *
171  k = min( m, n )
172  IF( k.EQ.0 ) RETURN
173 *
174 * Blocked loop of length K
175 *
176  DO i = 1, k, mb
177  ib = min( k-i+1, mb )
178 *
179 * Compute the LQ factorization of the current block A(I:M,I:I+IB-1)
180 *
181  CALL cgelqt3( ib, n-i+1, a(i,i), lda, t(1,i), ldt, iinfo )
182  IF( i+ib.LE.m ) THEN
183 *
184 * Update by applying H**T to A(I:M,I+IB:N) from the right
185 *
186  CALL clarfb( 'R', 'N', 'F', 'R', m-i-ib+1, n-i+1, ib,
187  $ a( i, i ), lda, t( 1, i ), ldt,
188  $ a( i+ib, i ), lda, work , m-i-ib+1 )
189  END IF
190  END DO
191  RETURN
192 *
193 * End of CGELQT
194 *
195  END
cgelqt3
recursive subroutine cgelqt3(M, N, A, LDA, T, LDT, INFO)
CGELQT3
Definition: cgelqt3.f:118
cgelqt
subroutine cgelqt(M, N, MB, A, LDA, T, LDT, WORK, INFO)
CGELQT
Definition: cgelqt.f:126
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
clarfb
subroutine clarfb(SIDE, TRANS, DIRECT, STOREV, M, N, K, V, LDV, T, LDT, C, LDC, WORK, LDWORK)
CLARFB applies a block reflector or its conjugate-transpose to a general rectangular matrix.
Definition: clarfb.f:199