LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
sgeqrt3.f
Go to the documentation of this file.
1 *> \brief \b SGEQRT3 recursively computes a QR factorization of a general real or complex matrix using the compact WY representation of Q.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SGEQRT3 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sgeqrt3.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sgeqrt3.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sgeqrt3.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * RECURSIVE SUBROUTINE SGEQRT3( M, N, A, LDA, T, LDT, INFO )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, M, N, LDT
25 * ..
26 * .. Array Arguments ..
27 * REAL A( LDA, * ), T( LDT, * )
28 * ..
29 *
30 *
31 *> \par Purpose:
32 * =============
33 *>
34 *> \verbatim
35 *>
36 *> SGEQRT3 recursively computes a QR factorization of a real M-by-N
37 *> matrix A, using the compact WY representation of Q.
38 *>
39 *> Based on the algorithm of Elmroth and Gustavson,
40 *> IBM J. Res. Develop. Vol 44 No. 4 July 2000.
41 *> \endverbatim
42 *
43 * Arguments:
44 * ==========
45 *
46 *> \param[in] M
47 *> \verbatim
48 *> M is INTEGER
49 *> The number of rows of the matrix A. M >= N.
50 *> \endverbatim
51 *>
52 *> \param[in] N
53 *> \verbatim
54 *> N is INTEGER
55 *> The number of columns of the matrix A. N >= 0.
56 *> \endverbatim
57 *>
58 *> \param[in,out] A
59 *> \verbatim
60 *> A is REAL array, dimension (LDA,N)
61 *> On entry, the real M-by-N matrix A. On exit, the elements on and
62 *> above the diagonal contain the N-by-N upper triangular matrix R; the
63 *> elements below the diagonal are the columns of V. See below for
64 *> further details.
65 *> \endverbatim
66 *>
67 *> \param[in] LDA
68 *> \verbatim
69 *> LDA is INTEGER
70 *> The leading dimension of the array A. LDA >= max(1,M).
71 *> \endverbatim
72 *>
73 *> \param[out] T
74 *> \verbatim
75 *> T is REAL array, dimension (LDT,N)
76 *> The N-by-N upper triangular factor of the block reflector.
77 *> The elements on and above the diagonal contain the block
78 *> reflector T; the elements below the diagonal are not used.
79 *> See below for further details.
80 *> \endverbatim
81 *>
82 *> \param[in] LDT
83 *> \verbatim
84 *> LDT is INTEGER
85 *> The leading dimension of the array T. LDT >= max(1,N).
86 *> \endverbatim
87 *>
88 *> \param[out] INFO
89 *> \verbatim
90 *> INFO is INTEGER
91 *> = 0: successful exit
92 *> < 0: if INFO = -i, the i-th argument had an illegal value
93 *> \endverbatim
94 *
95 * Authors:
96 * ========
97 *
98 *> \author Univ. of Tennessee
99 *> \author Univ. of California Berkeley
100 *> \author Univ. of Colorado Denver
101 *> \author NAG Ltd.
102 *
103 *> \date September 2012
104 *
105 *> \ingroup realGEcomputational
106 *
107 *> \par Further Details:
108 * =====================
109 *>
110 *> \verbatim
111 *>
112 *> The matrix V stores the elementary reflectors H(i) in the i-th column
113 *> below the diagonal. For example, if M=5 and N=3, the matrix V is
114 *>
115 *> V = ( 1 )
116 *> ( v1 1 )
117 *> ( v1 v2 1 )
118 *> ( v1 v2 v3 )
119 *> ( v1 v2 v3 )
120 *>
121 *> where the vi's represent the vectors which define H(i), which are returned
122 *> in the matrix A. The 1's along the diagonal of V are not stored in A. The
123 *> block reflector H is then given by
124 *>
125 *> H = I - V * T * V**T
126 *>
127 *> where V**T is the transpose of V.
128 *>
129 *> For details of the algorithm, see Elmroth and Gustavson (cited above).
130 *> \endverbatim
131 *>
132 * =====================================================================
133  RECURSIVE SUBROUTINE sgeqrt3( M, N, A, LDA, T, LDT, INFO )
134 *
135 * -- LAPACK computational routine (version 3.4.2) --
136 * -- LAPACK is a software package provided by Univ. of Tennessee, --
137 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
138 * September 2012
139 *
140 * .. Scalar Arguments ..
141  INTEGER info, lda, m, n, ldt
142 * ..
143 * .. Array Arguments ..
144  REAL a( lda, * ), t( ldt, * )
145 * ..
146 *
147 * =====================================================================
148 *
149 * .. Parameters ..
150  REAL one
151  parameter( one = 1.0 )
152 * ..
153 * .. Local Scalars ..
154  INTEGER i, i1, j, j1, n1, n2, iinfo
155 * ..
156 * .. External Subroutines ..
157  EXTERNAL slarfg, strmm, sgemm, xerbla
158 * ..
159 * .. Executable Statements ..
160 *
161  info = 0
162  IF( n .LT. 0 ) THEN
163  info = -2
164  ELSE IF( m .LT. n ) THEN
165  info = -1
166  ELSE IF( lda .LT. max( 1, m ) ) THEN
167  info = -4
168  ELSE IF( ldt .LT. max( 1, n ) ) THEN
169  info = -6
170  END IF
171  IF( info.NE.0 ) THEN
172  CALL xerbla( 'SGEQRT3', -info )
173  return
174  END IF
175 *
176  IF( n.EQ.1 ) THEN
177 *
178 * Compute Householder transform when N=1
179 *
180  CALL slarfg( m, a, a( min( 2, m ), 1 ), 1, t )
181 *
182  ELSE
183 *
184 * Otherwise, split A into blocks...
185 *
186  n1 = n/2
187  n2 = n-n1
188  j1 = min( n1+1, n )
189  i1 = min( n+1, m )
190 *
191 * Compute A(1:M,1:N1) <- (Y1,R1,T1), where Q1 = I - Y1 T1 Y1^H
192 *
193  CALL sgeqrt3( m, n1, a, lda, t, ldt, iinfo )
194 *
195 * Compute A(1:M,J1:N) = Q1^H A(1:M,J1:N) [workspace: T(1:N1,J1:N)]
196 *
197  DO j=1,n2
198  DO i=1,n1
199  t( i, j+n1 ) = a( i, j+n1 )
200  END DO
201  END DO
202  CALL strmm( 'L', 'L', 'T', 'U', n1, n2, one,
203  & a, lda, t( 1, j1 ), ldt )
204 *
205  CALL sgemm( 'T', 'N', n1, n2, m-n1, one, a( j1, 1 ), lda,
206  & a( j1, j1 ), lda, one, t( 1, j1 ), ldt)
207 *
208  CALL strmm( 'L', 'U', 'T', 'N', n1, n2, one,
209  & t, ldt, t( 1, j1 ), ldt )
210 *
211  CALL sgemm( 'N', 'N', m-n1, n2, n1, -one, a( j1, 1 ), lda,
212  & t( 1, j1 ), ldt, one, a( j1, j1 ), lda )
213 *
214  CALL strmm( 'L', 'L', 'N', 'U', n1, n2, one,
215  & a, lda, t( 1, j1 ), ldt )
216 *
217  DO j=1,n2
218  DO i=1,n1
219  a( i, j+n1 ) = a( i, j+n1 ) - t( i, j+n1 )
220  END DO
221  END DO
222 *
223 * Compute A(J1:M,J1:N) <- (Y2,R2,T2) where Q2 = I - Y2 T2 Y2^H
224 *
225  CALL sgeqrt3( m-n1, n2, a( j1, j1 ), lda,
226  & t( j1, j1 ), ldt, iinfo )
227 *
228 * Compute T3 = T(1:N1,J1:N) = -T1 Y1^H Y2 T2
229 *
230  DO i=1,n1
231  DO j=1,n2
232  t( i, j+n1 ) = (a( j+n1, i ))
233  END DO
234  END DO
235 *
236  CALL strmm( 'R', 'L', 'N', 'U', n1, n2, one,
237  & a( j1, j1 ), lda, t( 1, j1 ), ldt )
238 *
239  CALL sgemm( 'T', 'N', n1, n2, m-n, one, a( i1, 1 ), lda,
240  & a( i1, j1 ), lda, one, t( 1, j1 ), ldt )
241 *
242  CALL strmm( 'L', 'U', 'N', 'N', n1, n2, -one, t, ldt,
243  & t( 1, j1 ), ldt )
244 *
245  CALL strmm( 'R', 'U', 'N', 'N', n1, n2, one,
246  & t( j1, j1 ), ldt, t( 1, j1 ), ldt )
247 *
248 * Y = (Y1,Y2); R = [ R1 A(1:N1,J1:N) ]; T = [T1 T3]
249 * [ 0 R2 ] [ 0 T2]
250 *
251  END IF
252 *
253  return
254 *
255 * End of SGEQRT3
256 *
257  END