LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dorbdb4.f
Go to the documentation of this file.
1 *> \brief \b DORBDB4
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DORBDB4 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dorbdb4.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dorbdb4.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorbdb4.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DORBDB4( 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 * DOUBLE PRECISION PHI(*), THETA(*)
30 * DOUBLE PRECISION PHANTOM(*), TAUP1(*), TAUP2(*), TAUQ1(*),
31 * $ WORK(*), X11(LDX11,*), X21(LDX21,*)
32 * ..
33 *
34 *
35 *> \par Purpose:
36 *> =============
37 *>
38 *>\verbatim
39 *>
40 *> DORBDB4 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 DORBDB1, DORBDB2, and DORBDB3 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 * Authors:
179 * ========
180 *
181 *> \author Univ. of Tennessee
182 *> \author Univ. of California Berkeley
183 *> \author Univ. of Colorado Denver
184 *> \author NAG Ltd.
185 *
186 *> \date July 2012
187 *
188 *> \ingroup doubleOTHERcomputational
189 *
190 *> \par Further Details:
191 * =====================
192 *>
193 *> \verbatim
194 *>
195 *> The upper-bidiagonal blocks B11, B21 are represented implicitly by
196 *> angles THETA(1), ..., THETA(Q) and PHI(1), ..., PHI(Q-1). Every entry
197 *> in each bidiagonal band is a product of a sine or cosine of a THETA
198 *> with a sine or cosine of a PHI. See [1] or DORCSD for details.
199 *>
200 *> P1, P2, and Q1 are represented as products of elementary reflectors.
201 *> See DORCSD2BY1 for details on generating P1, P2, and Q1 using DORGQR
202 *> and DORGLQ.
203 *> \endverbatim
204 *
205 *> \par References:
206 * ================
207 *>
208 *> [1] Brian D. Sutton. Computing the complete CS decomposition. Numer.
209 *> Algorithms, 50(1):33-65, 2009.
210 *>
211 * =====================================================================
212  SUBROUTINE dorbdb4( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
213  $ taup1, taup2, tauq1, phantom, work, lwork,
214  $ info )
215 *
216 * -- LAPACK computational routine (version 3.6.1) --
217 * -- LAPACK is a software package provided by Univ. of Tennessee, --
218 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
219 * July 2012
220 *
221 * .. Scalar Arguments ..
222  INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
223 * ..
224 * .. Array Arguments ..
225  DOUBLE PRECISION PHI(*), THETA(*)
226  DOUBLE PRECISION PHANTOM(*), TAUP1(*), TAUP2(*), TAUQ1(*),
227  $ work(*), x11(ldx11,*), x21(ldx21,*)
228 * ..
229 *
230 * ====================================================================
231 *
232 * .. Parameters ..
233  DOUBLE PRECISION NEGONE, ONE, ZERO
234  parameter ( negone = -1.0d0, one = 1.0d0, zero = 0.0d0 )
235 * ..
236 * .. Local Scalars ..
237  DOUBLE PRECISION C, S
238  INTEGER CHILDINFO, I, ILARF, IORBDB5, J, LLARF,
239  $ lorbdb5, lworkmin, lworkopt
240  LOGICAL LQUERY
241 * ..
242 * .. External Subroutines ..
243  EXTERNAL dlarf, dlarfgp, dorbdb5, drot, dscal, xerbla
244 * ..
245 * .. External Functions ..
246  DOUBLE PRECISION DNRM2
247  EXTERNAL dnrm2
248 * ..
249 * .. Intrinsic Function ..
250  INTRINSIC atan2, cos, max, sin, sqrt
251 * ..
252 * .. Executable Statements ..
253 *
254 * Test input arguments
255 *
256  info = 0
257  lquery = lwork .EQ. -1
258 *
259  IF( m .LT. 0 ) THEN
260  info = -1
261  ELSE IF( p .LT. m-q .OR. m-p .LT. m-q ) THEN
262  info = -2
263  ELSE IF( q .LT. m-q .OR. q .GT. m ) THEN
264  info = -3
265  ELSE IF( ldx11 .LT. max( 1, p ) ) THEN
266  info = -5
267  ELSE IF( ldx21 .LT. max( 1, m-p ) ) THEN
268  info = -7
269  END IF
270 *
271 * Compute workspace
272 *
273  IF( info .EQ. 0 ) THEN
274  ilarf = 2
275  llarf = max( q-1, p-1, m-p-1 )
276  iorbdb5 = 2
277  lorbdb5 = q
278  lworkopt = ilarf + llarf - 1
279  lworkopt = max( lworkopt, iorbdb5 + lorbdb5 - 1 )
280  lworkmin = lworkopt
281  work(1) = lworkopt
282  IF( lwork .LT. lworkmin .AND. .NOT.lquery ) THEN
283  info = -14
284  END IF
285  END IF
286  IF( info .NE. 0 ) THEN
287  CALL xerbla( 'DORBDB4', -info )
288  RETURN
289  ELSE IF( lquery ) THEN
290  RETURN
291  END IF
292 *
293 * Reduce columns 1, ..., M-Q of X11 and X21
294 *
295  DO i = 1, m-q
296 *
297  IF( i .EQ. 1 ) THEN
298  DO j = 1, m
299  phantom(j) = zero
300  END DO
301  CALL dorbdb5( p, m-p, q, phantom(1), 1, phantom(p+1), 1,
302  $ x11, ldx11, x21, ldx21, work(iorbdb5),
303  $ lorbdb5, childinfo )
304  CALL dscal( p, negone, phantom(1), 1 )
305  CALL dlarfgp( p, phantom(1), phantom(2), 1, taup1(1) )
306  CALL dlarfgp( m-p, phantom(p+1), phantom(p+2), 1, taup2(1) )
307  theta(i) = atan2( phantom(1), phantom(p+1) )
308  c = cos( theta(i) )
309  s = sin( theta(i) )
310  phantom(1) = one
311  phantom(p+1) = one
312  CALL dlarf( 'L', p, q, phantom(1), 1, taup1(1), x11, ldx11,
313  $ work(ilarf) )
314  CALL dlarf( 'L', m-p, q, phantom(p+1), 1, taup2(1), x21,
315  $ ldx21, work(ilarf) )
316  ELSE
317  CALL dorbdb5( p-i+1, m-p-i+1, q-i+1, x11(i,i-1), 1,
318  $ x21(i,i-1), 1, x11(i,i), ldx11, x21(i,i),
319  $ ldx21, work(iorbdb5), lorbdb5, childinfo )
320  CALL dscal( p-i+1, negone, x11(i,i-1), 1 )
321  CALL dlarfgp( p-i+1, x11(i,i-1), x11(i+1,i-1), 1, taup1(i) )
322  CALL dlarfgp( m-p-i+1, x21(i,i-1), x21(i+1,i-1), 1,
323  $ taup2(i) )
324  theta(i) = atan2( x11(i,i-1), x21(i,i-1) )
325  c = cos( theta(i) )
326  s = sin( theta(i) )
327  x11(i,i-1) = one
328  x21(i,i-1) = one
329  CALL dlarf( 'L', p-i+1, q-i+1, x11(i,i-1), 1, taup1(i),
330  $ x11(i,i), ldx11, work(ilarf) )
331  CALL dlarf( 'L', m-p-i+1, q-i+1, x21(i,i-1), 1, taup2(i),
332  $ x21(i,i), ldx21, work(ilarf) )
333  END IF
334 *
335  CALL drot( q-i+1, x11(i,i), ldx11, x21(i,i), ldx21, s, -c )
336  CALL dlarfgp( q-i+1, x21(i,i), x21(i,i+1), ldx21, tauq1(i) )
337  c = x21(i,i)
338  x21(i,i) = one
339  CALL dlarf( 'R', p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
340  $ x11(i+1,i), ldx11, work(ilarf) )
341  CALL dlarf( 'R', m-p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
342  $ x21(i+1,i), ldx21, work(ilarf) )
343  IF( i .LT. m-q ) THEN
344  s = sqrt( dnrm2( p-i, x11(i+1,i), 1 )**2
345  $ + dnrm2( m-p-i, x21(i+1,i), 1 )**2 )
346  phi(i) = atan2( s, c )
347  END IF
348 *
349  END DO
350 *
351 * Reduce the bottom-right portion of X11 to [ I 0 ]
352 *
353  DO i = m - q + 1, p
354  CALL dlarfgp( q-i+1, x11(i,i), x11(i,i+1), ldx11, tauq1(i) )
355  x11(i,i) = one
356  CALL dlarf( 'R', p-i, q-i+1, x11(i,i), ldx11, tauq1(i),
357  $ x11(i+1,i), ldx11, work(ilarf) )
358  CALL dlarf( 'R', q-p, q-i+1, x11(i,i), ldx11, tauq1(i),
359  $ x21(m-q+1,i), ldx21, work(ilarf) )
360  END DO
361 *
362 * Reduce the bottom-right portion of X21 to [ 0 I ]
363 *
364  DO i = p + 1, q
365  CALL dlarfgp( q-i+1, x21(m-q+i-p,i), x21(m-q+i-p,i+1), ldx21,
366  $ tauq1(i) )
367  x21(m-q+i-p,i) = one
368  CALL dlarf( 'R', q-i, q-i+1, x21(m-q+i-p,i), ldx21, tauq1(i),
369  $ x21(m-q+i-p+1,i), ldx21, work(ilarf) )
370  END DO
371 *
372  RETURN
373 *
374 * End of DORBDB4
375 *
376  END
377 
subroutine dlarfgp(N, ALPHA, X, INCX, TAU)
DLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.
Definition: dlarfgp.f:106
subroutine drot(N, DX, INCX, DY, INCY, C, S)
DROT
Definition: drot.f:53
subroutine dlarf(SIDE, M, N, V, INCV, TAU, C, LDC, WORK)
DLARF applies an elementary reflector to a general rectangular matrix.
Definition: dlarf.f:126
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine dorbdb5(M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2, LDQ2, WORK, LWORK, INFO)
DORBDB5
Definition: dorbdb5.f:158
subroutine dscal(N, DA, DX, INCX)
DSCAL
Definition: dscal.f:55
subroutine dorbdb4(M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI, TAUP1, TAUP2, TAUQ1, PHANTOM, WORK, LWORK, INFO)
DORBDB4
Definition: dorbdb4.f:215