LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sorbdb1.f
Go to the documentation of this file.
1*> \brief \b SORBDB1
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SORBDB1 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sorbdb1.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sorbdb1.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sorbdb1.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE SORBDB1( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
22* TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO )
23*
24* .. Scalar Arguments ..
25* INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
26* ..
27* .. Array Arguments ..
28* REAL PHI(*), THETA(*)
29* REAL TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
30* $ X11(LDX11,*), X21(LDX21,*)
31* ..
32*
33*
34*> \par Purpose:
35* =============
36*>
37*>\verbatim
38*>
39*> SORBDB1 simultaneously bidiagonalizes the blocks of a tall and skinny
40*> matrix X with orthonormal columns:
41*>
42*> [ B11 ]
43*> [ X11 ] [ P1 | ] [ 0 ]
44*> [-----] = [---------] [-----] Q1**T .
45*> [ X21 ] [ | P2 ] [ B21 ]
46*> [ 0 ]
47*>
48*> X11 is P-by-Q, and X21 is (M-P)-by-Q. Q must be no larger than P,
49*> M-P, or M-Q. Routines SORBDB2, SORBDB3, and SORBDB4 handle cases in
50*> which Q is not the minimum dimension.
51*>
52*> The orthogonal matrices P1, P2, and Q1 are P-by-P, (M-P)-by-(M-P),
53*> and (M-Q)-by-(M-Q), respectively. They are represented implicitly by
54*> Householder vectors.
55*>
56*> B11 and B12 are Q-by-Q bidiagonal matrices represented implicitly by
57*> angles THETA, PHI.
58*>
59*>\endverbatim
60*
61* Arguments:
62* ==========
63*
64*> \param[in] M
65*> \verbatim
66*> M is INTEGER
67*> The number of rows X11 plus the number of rows in X21.
68*> \endverbatim
69*>
70*> \param[in] P
71*> \verbatim
72*> P is INTEGER
73*> The number of rows in X11. 0 <= P <= M.
74*> \endverbatim
75*>
76*> \param[in] Q
77*> \verbatim
78*> Q is INTEGER
79*> The number of columns in X11 and X21. 0 <= Q <=
80*> MIN(P,M-P,M-Q).
81*> \endverbatim
82*>
83*> \param[in,out] X11
84*> \verbatim
85*> X11 is REAL array, dimension (LDX11,Q)
86*> On entry, the top block of the matrix X to be reduced. On
87*> exit, the columns of tril(X11) specify reflectors for P1 and
88*> the rows of triu(X11,1) specify reflectors for Q1.
89*> \endverbatim
90*>
91*> \param[in] LDX11
92*> \verbatim
93*> LDX11 is INTEGER
94*> The leading dimension of X11. LDX11 >= P.
95*> \endverbatim
96*>
97*> \param[in,out] X21
98*> \verbatim
99*> X21 is REAL array, dimension (LDX21,Q)
100*> On entry, the bottom block of the matrix X to be reduced. On
101*> exit, the columns of tril(X21) specify reflectors for P2.
102*> \endverbatim
103*>
104*> \param[in] LDX21
105*> \verbatim
106*> LDX21 is INTEGER
107*> The leading dimension of X21. LDX21 >= M-P.
108*> \endverbatim
109*>
110*> \param[out] THETA
111*> \verbatim
112*> THETA is REAL array, dimension (Q)
113*> The entries of the bidiagonal blocks B11, B21 are defined by
114*> THETA and PHI. See Further Details.
115*> \endverbatim
116*>
117*> \param[out] PHI
118*> \verbatim
119*> PHI is REAL array, dimension (Q-1)
120*> The entries of the bidiagonal blocks B11, B21 are defined by
121*> THETA and PHI. See Further Details.
122*> \endverbatim
123*>
124*> \param[out] TAUP1
125*> \verbatim
126*> TAUP1 is REAL array, dimension (P)
127*> The scalar factors of the elementary reflectors that define
128*> P1.
129*> \endverbatim
130*>
131*> \param[out] TAUP2
132*> \verbatim
133*> TAUP2 is REAL array, dimension (M-P)
134*> The scalar factors of the elementary reflectors that define
135*> P2.
136*> \endverbatim
137*>
138*> \param[out] TAUQ1
139*> \verbatim
140*> TAUQ1 is REAL array, dimension (Q)
141*> The scalar factors of the elementary reflectors that define
142*> Q1.
143*> \endverbatim
144*>
145*> \param[out] WORK
146*> \verbatim
147*> WORK is REAL array, dimension (LWORK)
148*> \endverbatim
149*>
150*> \param[in] LWORK
151*> \verbatim
152*> LWORK is INTEGER
153*> The dimension of the array WORK. LWORK >= M-Q.
154*>
155*> If LWORK = -1, then a workspace query is assumed; the routine
156*> only calculates the optimal size of the WORK array, returns
157*> this value as the first entry of the WORK array, and no error
158*> message related to LWORK is issued by XERBLA.
159*> \endverbatim
160*>
161*> \param[out] INFO
162*> \verbatim
163*> INFO is INTEGER
164*> = 0: successful exit.
165*> < 0: if INFO = -i, the i-th argument had an illegal value.
166*> \endverbatim
167*>
168*
169* Authors:
170* ========
171*
172*> \author Univ. of Tennessee
173*> \author Univ. of California Berkeley
174*> \author Univ. of Colorado Denver
175*> \author NAG Ltd.
176*
177*> \ingroup unbdb1
178*
179*> \par Further Details:
180* =====================
181*>
182*> \verbatim
183*>
184*> The upper-bidiagonal blocks B11, B21 are represented implicitly by
185*> angles THETA(1), ..., THETA(Q) and PHI(1), ..., PHI(Q-1). Every entry
186*> in each bidiagonal band is a product of a sine or cosine of a THETA
187*> with a sine or cosine of a PHI. See [1] or SORCSD for details.
188*>
189*> P1, P2, and Q1 are represented as products of elementary reflectors.
190*> See SORCSD2BY1 for details on generating P1, P2, and Q1 using SORGQR
191*> and SORGLQ.
192*> \endverbatim
193*
194*> \par References:
195* ================
196*>
197*> [1] Brian D. Sutton. Computing the complete CS decomposition. Numer.
198*> Algorithms, 50(1):33-65, 2009.
199*>
200* =====================================================================
201 SUBROUTINE sorbdb1( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
202 $ TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO )
203*
204* -- LAPACK computational routine --
205* -- LAPACK is a software package provided by Univ. of Tennessee, --
206* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
207*
208* .. Scalar Arguments ..
209 INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
210* ..
211* .. Array Arguments ..
212 REAL PHI(*), THETA(*)
213 REAL TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
214 $ x11(ldx11,*), x21(ldx21,*)
215* ..
216*
217* ====================================================================
218*
219* .. Parameters ..
220 REAL ONE
221 parameter( one = 1.0e0 )
222* ..
223* .. Local Scalars ..
224 REAL C, S
225 INTEGER CHILDINFO, I, ILARF, IORBDB5, LLARF, LORBDB5,
226 $ lworkmin, lworkopt
227 LOGICAL LQUERY
228* ..
229* .. External Subroutines ..
230 EXTERNAL slarf, slarfgp, sorbdb5, srot, xerbla
231* ..
232* .. External Functions ..
233 REAL SNRM2
234 EXTERNAL snrm2
235* ..
236* .. Intrinsic Function ..
237 INTRINSIC atan2, cos, max, sin, sqrt
238* ..
239* .. Executable Statements ..
240*
241* Test input arguments
242*
243 info = 0
244 lquery = lwork .EQ. -1
245*
246 IF( m .LT. 0 ) THEN
247 info = -1
248 ELSE IF( p .LT. q .OR. m-p .LT. q ) THEN
249 info = -2
250 ELSE IF( q .LT. 0 .OR. m-q .LT. q ) THEN
251 info = -3
252 ELSE IF( ldx11 .LT. max( 1, p ) ) THEN
253 info = -5
254 ELSE IF( ldx21 .LT. max( 1, m-p ) ) THEN
255 info = -7
256 END IF
257*
258* Compute workspace
259*
260 IF( info .EQ. 0 ) THEN
261 ilarf = 2
262 llarf = max( p-1, m-p-1, q-1 )
263 iorbdb5 = 2
264 lorbdb5 = q-2
265 lworkopt = max( ilarf+llarf-1, iorbdb5+lorbdb5-1 )
266 lworkmin = lworkopt
267 work(1) = lworkopt
268 IF( lwork .LT. lworkmin .AND. .NOT.lquery ) THEN
269 info = -14
270 END IF
271 END IF
272 IF( info .NE. 0 ) THEN
273 CALL xerbla( 'SORBDB1', -info )
274 RETURN
275 ELSE IF( lquery ) THEN
276 RETURN
277 END IF
278*
279* Reduce columns 1, ..., Q of X11 and X21
280*
281 DO i = 1, q
282*
283 CALL slarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
284 CALL slarfgp( m-p-i+1, x21(i,i), x21(i+1,i), 1, taup2(i) )
285 theta(i) = atan2( x21(i,i), x11(i,i) )
286 c = cos( theta(i) )
287 s = sin( theta(i) )
288 x11(i,i) = one
289 x21(i,i) = one
290 CALL slarf( 'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,i+1),
291 $ ldx11, work(ilarf) )
292 CALL slarf( 'L', m-p-i+1, q-i, x21(i,i), 1, taup2(i),
293 $ x21(i,i+1), ldx21, work(ilarf) )
294*
295 IF( i .LT. q ) THEN
296 CALL srot( q-i, x11(i,i+1), ldx11, x21(i,i+1), ldx21, c, s )
297 CALL slarfgp( q-i, x21(i,i+1), x21(i,i+2), ldx21, tauq1(i) )
298 s = x21(i,i+1)
299 x21(i,i+1) = one
300 CALL slarf( 'R', p-i, q-i, x21(i,i+1), ldx21, tauq1(i),
301 $ x11(i+1,i+1), ldx11, work(ilarf) )
302 CALL slarf( 'R', m-p-i, q-i, x21(i,i+1), ldx21, tauq1(i),
303 $ x21(i+1,i+1), ldx21, work(ilarf) )
304 c = sqrt( snrm2( p-i, x11(i+1,i+1), 1 )**2
305 $ + snrm2( m-p-i, x21(i+1,i+1), 1 )**2 )
306 phi(i) = atan2( s, c )
307 CALL sorbdb5( p-i, m-p-i, q-i-1, x11(i+1,i+1), 1,
308 $ x21(i+1,i+1), 1, x11(i+1,i+2), ldx11,
309 $ x21(i+1,i+2), ldx21, work(iorbdb5), lorbdb5,
310 $ childinfo )
311 END IF
312*
313 END DO
314*
315 RETURN
316*
317* End of SORBDB1
318*
319 END
320
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine slarf(side, m, n, v, incv, tau, c, ldc, work)
SLARF applies an elementary reflector to a general rectangular matrix.
Definition slarf.f:124
subroutine slarfgp(n, alpha, x, incx, tau)
SLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.
Definition slarfgp.f:104
subroutine srot(n, sx, incx, sy, incy, c, s)
SROT
Definition srot.f:92
subroutine sorbdb1(m, p, q, x11, ldx11, x21, ldx21, theta, phi, taup1, taup2, tauq1, work, lwork, info)
SORBDB1
Definition sorbdb1.f:203
subroutine sorbdb5(m1, m2, n, x1, incx1, x2, incx2, q1, ldq1, q2, ldq2, work, lwork, info)
SORBDB5
Definition sorbdb5.f:156