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