LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dorbdb3.f
Go to the documentation of this file.
1 *> \brief \b DORBDB3
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DORBDB3 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dorbdb3.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dorbdb3.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorbdb3.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DORBDB3( 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 * DOUBLE PRECISION PHI(*), THETA(*)
29 * DOUBLE PRECISION TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
30 * $ X11(LDX11,*), X21(LDX21,*)
31 * ..
32 *
33 *
34 *> \par Purpose:
35 *> =============
36 *>
37 *>\verbatim
38 *>
39 *> DORBDB3 simultaneously bidiagonalizes the blocks of a tall and skinny
40 *> matrix X with orthonomal 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. M-P must be no larger than P,
49 *> Q, or M-Q. Routines DORBDB1, DORBDB2, and DORBDB4 handle cases in
50 *> which M-P 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 (M-P)-by-(M-P) bidiagonal matrices represented
57 *> implicitly by 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. M-P <= min(P,Q,M-Q).
74 *> \endverbatim
75 *>
76 *> \param[in] Q
77 *> \verbatim
78 *> Q is INTEGER
79 *> The number of columns in X11 and X21. 0 <= Q <= M.
80 *> \endverbatim
81 *>
82 *> \param[in,out] X11
83 *> \verbatim
84 *> X11 is DOUBLE PRECISION array, dimension (LDX11,Q)
85 *> On entry, the top block of the matrix X to be reduced. On
86 *> exit, the columns of tril(X11) specify reflectors for P1 and
87 *> the rows of triu(X11,1) specify reflectors for Q1.
88 *> \endverbatim
89 *>
90 *> \param[in] LDX11
91 *> \verbatim
92 *> LDX11 is INTEGER
93 *> The leading dimension of X11. LDX11 >= P.
94 *> \endverbatim
95 *>
96 *> \param[in,out] X21
97 *> \verbatim
98 *> X21 is DOUBLE PRECISION array, dimension (LDX21,Q)
99 *> On entry, the bottom block of the matrix X to be reduced. On
100 *> exit, the columns of tril(X21) specify reflectors for P2.
101 *> \endverbatim
102 *>
103 *> \param[in] LDX21
104 *> \verbatim
105 *> LDX21 is INTEGER
106 *> The leading dimension of X21. LDX21 >= M-P.
107 *> \endverbatim
108 *>
109 *> \param[out] THETA
110 *> \verbatim
111 *> THETA is DOUBLE PRECISION array, dimension (Q)
112 *> The entries of the bidiagonal blocks B11, B21 are defined by
113 *> THETA and PHI. See Further Details.
114 *> \endverbatim
115 *>
116 *> \param[out] PHI
117 *> \verbatim
118 *> PHI is DOUBLE PRECISION array, dimension (Q-1)
119 *> The entries of the bidiagonal blocks B11, B21 are defined by
120 *> THETA and PHI. See Further Details.
121 *> \endverbatim
122 *>
123 *> \param[out] TAUP1
124 *> \verbatim
125 *> TAUP1 is DOUBLE PRECISION array, dimension (P)
126 *> The scalar factors of the elementary reflectors that define
127 *> P1.
128 *> \endverbatim
129 *>
130 *> \param[out] TAUP2
131 *> \verbatim
132 *> TAUP2 is DOUBLE PRECISION array, dimension (M-P)
133 *> The scalar factors of the elementary reflectors that define
134 *> P2.
135 *> \endverbatim
136 *>
137 *> \param[out] TAUQ1
138 *> \verbatim
139 *> TAUQ1 is DOUBLE PRECISION array, dimension (Q)
140 *> The scalar factors of the elementary reflectors that define
141 *> Q1.
142 *> \endverbatim
143 *>
144 *> \param[out] WORK
145 *> \verbatim
146 *> WORK is DOUBLE PRECISION array, dimension (LWORK)
147 *> \endverbatim
148 *>
149 *> \param[in] LWORK
150 *> \verbatim
151 *> LWORK is INTEGER
152 *> The dimension of the array WORK. LWORK >= M-Q.
153 *>
154 *> If LWORK = -1, then a workspace query is assumed; the routine
155 *> only calculates the optimal size of the WORK array, returns
156 *> this value as the first entry of the WORK array, and no error
157 *> message related to LWORK is issued by XERBLA.
158 *> \endverbatim
159 *>
160 *> \param[out] INFO
161 *> \verbatim
162 *> INFO is INTEGER
163 *> = 0: successful exit.
164 *> < 0: if INFO = -i, the i-th argument had an illegal value.
165 *> \endverbatim
166 *
167 * Authors:
168 * ========
169 *
170 *> \author Univ. of Tennessee
171 *> \author Univ. of California Berkeley
172 *> \author Univ. of Colorado Denver
173 *> \author NAG Ltd.
174 *
175 *> \date July 2012
176 *
177 *> \ingroup doubleOTHERcomputational
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 DORCSD for details.
188 *>
189 *> P1, P2, and Q1 are represented as products of elementary reflectors.
190 *> See DORCSD2BY1 for details on generating P1, P2, and Q1 using DORGQR
191 *> and DORGLQ.
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 dorbdb3( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
202  $ taup1, taup2, tauq1, work, lwork, info )
203 *
204 * -- LAPACK computational routine (version 3.6.1) --
205 * -- LAPACK is a software package provided by Univ. of Tennessee, --
206 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
207 * July 2012
208 *
209 * .. Scalar Arguments ..
210  INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
211 * ..
212 * .. Array Arguments ..
213  DOUBLE PRECISION PHI(*), THETA(*)
214  DOUBLE PRECISION TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
215  $ x11(ldx11,*), x21(ldx21,*)
216 * ..
217 *
218 * ====================================================================
219 *
220 * .. Parameters ..
221  DOUBLE PRECISION ONE
222  parameter ( one = 1.0d0 )
223 * ..
224 * .. Local Scalars ..
225  DOUBLE PRECISION C, S
226  INTEGER CHILDINFO, I, ILARF, IORBDB5, LLARF, LORBDB5,
227  $ lworkmin, lworkopt
228  LOGICAL LQUERY
229 * ..
230 * .. External Subroutines ..
231  EXTERNAL dlarf, dlarfgp, dorbdb5, drot, xerbla
232 * ..
233 * .. External Functions ..
234  DOUBLE PRECISION DNRM2
235  EXTERNAL dnrm2
236 * ..
237 * .. Intrinsic Function ..
238  INTRINSIC atan2, cos, max, sin, sqrt
239 * ..
240 * .. Executable Statements ..
241 *
242 * Test input arguments
243 *
244  info = 0
245  lquery = lwork .EQ. -1
246 *
247  IF( m .LT. 0 ) THEN
248  info = -1
249  ELSE IF( 2*p .LT. m .OR. p .GT. m ) THEN
250  info = -2
251  ELSE IF( q .LT. m-p .OR. m-q .LT. m-p ) THEN
252  info = -3
253  ELSE IF( ldx11 .LT. max( 1, p ) ) THEN
254  info = -5
255  ELSE IF( ldx21 .LT. max( 1, m-p ) ) THEN
256  info = -7
257  END IF
258 *
259 * Compute workspace
260 *
261  IF( info .EQ. 0 ) THEN
262  ilarf = 2
263  llarf = max( p, m-p-1, q-1 )
264  iorbdb5 = 2
265  lorbdb5 = q-1
266  lworkopt = max( ilarf+llarf-1, iorbdb5+lorbdb5-1 )
267  lworkmin = lworkopt
268  work(1) = lworkopt
269  IF( lwork .LT. lworkmin .AND. .NOT.lquery ) THEN
270  info = -14
271  END IF
272  END IF
273  IF( info .NE. 0 ) THEN
274  CALL xerbla( 'DORBDB3', -info )
275  RETURN
276  ELSE IF( lquery ) THEN
277  RETURN
278  END IF
279 *
280 * Reduce rows 1, ..., M-P of X11 and X21
281 *
282  DO i = 1, m-p
283 *
284  IF( i .GT. 1 ) THEN
285  CALL drot( q-i+1, x11(i-1,i), ldx11, x21(i,i), ldx11, c, s )
286  END IF
287 *
288  CALL dlarfgp( q-i+1, x21(i,i), x21(i,i+1), ldx21, tauq1(i) )
289  s = x21(i,i)
290  x21(i,i) = one
291  CALL dlarf( 'R', p-i+1, q-i+1, x21(i,i), ldx21, tauq1(i),
292  $ x11(i,i), ldx11, work(ilarf) )
293  CALL dlarf( 'R', m-p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
294  $ x21(i+1,i), ldx21, work(ilarf) )
295  c = sqrt( dnrm2( p-i+1, x11(i,i), 1 )**2
296  $ + dnrm2( m-p-i, x21(i+1,i), 1 )**2 )
297  theta(i) = atan2( s, c )
298 *
299  CALL dorbdb5( p-i+1, m-p-i, q-i, x11(i,i), 1, x21(i+1,i), 1,
300  $ x11(i,i+1), ldx11, x21(i+1,i+1), ldx21,
301  $ work(iorbdb5), lorbdb5, childinfo )
302  CALL dlarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
303  IF( i .LT. m-p ) THEN
304  CALL dlarfgp( m-p-i, x21(i+1,i), x21(i+2,i), 1, taup2(i) )
305  phi(i) = atan2( x21(i+1,i), x11(i,i) )
306  c = cos( phi(i) )
307  s = sin( phi(i) )
308  x21(i+1,i) = one
309  CALL dlarf( 'L', m-p-i, q-i, x21(i+1,i), 1, taup2(i),
310  $ x21(i+1,i+1), ldx21, work(ilarf) )
311  END IF
312  x11(i,i) = one
313  CALL dlarf( 'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,i+1),
314  $ ldx11, work(ilarf) )
315 *
316  END DO
317 *
318 * Reduce the bottom-right portion of X11 to the identity matrix
319 *
320  DO i = m-p + 1, q
321  CALL dlarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
322  x11(i,i) = one
323  CALL dlarf( 'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,i+1),
324  $ ldx11, work(ilarf) )
325  END DO
326 *
327  RETURN
328 *
329 * End of DORBDB3
330 *
331  END
332 
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 dorbdb3(M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI, TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO)
DORBDB3
Definition: dorbdb3.f:203