LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
zunbdb4.f
Go to the documentation of this file.
1 *> \brief \b ZUNBDB4
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZUNBDB4 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunbdb4.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunbdb4.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunbdb4.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZUNBDB4( 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 * COMPLEX*16 PHANTOM(*), TAUP1(*), TAUP2(*), TAUQ1(*),
31 * $ WORK(*), X11(LDX11,*), X21(LDX21,*)
32 * ..
33 *
34 *
35 *> \par Purpose:
36 * =============
37 *>
38 *>\verbatim
39 *>
40 *> ZUNBDB4 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 ZUNBDB1, ZUNBDB2, and ZUNBDB3 handle cases in
51 *> which M-Q is not the minimum dimension.
52 *>
53 *> The unitary 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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 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 complex16OTHERcomputational
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 ZUNCSD for details.
199 *>
200 *> P1, P2, and Q1 are represented as products of elementary reflectors.
201 *> See ZUNCSD2BY1 for details on generating P1, P2, and Q1 using ZUNGQR
202 *> and ZUNGLQ.
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 zunbdb4( 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.8.0) --
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  COMPLEX*16 PHANTOM(*), TAUP1(*), TAUP2(*), TAUQ1(*),
227  $ work(*), x11(ldx11,*), x21(ldx21,*)
228 * ..
229 *
230 * ====================================================================
231 *
232 * .. Parameters ..
233  COMPLEX*16 NEGONE, ONE, ZERO
234  PARAMETER ( NEGONE = (-1.0d0,0.0d0), one = (1.0d0,0.0d0),
235  $ zero = (0.0d0,0.0d0) )
236 * ..
237 * .. Local Scalars ..
238  DOUBLE PRECISION C, S
239  INTEGER CHILDINFO, I, ILARF, IORBDB5, J, LLARF,
240  $ lorbdb5, lworkmin, lworkopt
241  LOGICAL LQUERY
242 * ..
243 * .. External Subroutines ..
244  EXTERNAL zlarf, zlarfgp, zunbdb5, zdrot, zscal, zlacgv,
245  $ xerbla
246 * ..
247 * .. External Functions ..
248  DOUBLE PRECISION DZNRM2
249  EXTERNAL DZNRM2
250 * ..
251 * .. Intrinsic Function ..
252  INTRINSIC atan2, cos, max, sin, sqrt
253 * ..
254 * .. Executable Statements ..
255 *
256 * Test input arguments
257 *
258  info = 0
259  lquery = lwork .EQ. -1
260 *
261  IF( m .LT. 0 ) THEN
262  info = -1
263  ELSE IF( p .LT. m-q .OR. m-p .LT. m-q ) THEN
264  info = -2
265  ELSE IF( q .LT. m-q .OR. q .GT. m ) THEN
266  info = -3
267  ELSE IF( ldx11 .LT. max( 1, p ) ) THEN
268  info = -5
269  ELSE IF( ldx21 .LT. max( 1, m-p ) ) THEN
270  info = -7
271  END IF
272 *
273 * Compute workspace
274 *
275  IF( info .EQ. 0 ) THEN
276  ilarf = 2
277  llarf = max( q-1, p-1, m-p-1 )
278  iorbdb5 = 2
279  lorbdb5 = q
280  lworkopt = ilarf + llarf - 1
281  lworkopt = max( lworkopt, iorbdb5 + lorbdb5 - 1 )
282  lworkmin = lworkopt
283  work(1) = lworkopt
284  IF( lwork .LT. lworkmin .AND. .NOT.lquery ) THEN
285  info = -14
286  END IF
287  END IF
288  IF( info .NE. 0 ) THEN
289  CALL xerbla( 'ZUNBDB4', -info )
290  RETURN
291  ELSE IF( lquery ) THEN
292  RETURN
293  END IF
294 *
295 * Reduce columns 1, ..., M-Q of X11 and X21
296 *
297  DO i = 1, m-q
298 *
299  IF( i .EQ. 1 ) THEN
300  DO j = 1, m
301  phantom(j) = zero
302  END DO
303  CALL zunbdb5( p, m-p, q, phantom(1), 1, phantom(p+1), 1,
304  $ x11, ldx11, x21, ldx21, work(iorbdb5),
305  $ lorbdb5, childinfo )
306  CALL zscal( p, negone, phantom(1), 1 )
307  CALL zlarfgp( p, phantom(1), phantom(2), 1, taup1(1) )
308  CALL zlarfgp( m-p, phantom(p+1), phantom(p+2), 1, taup2(1) )
309  theta(i) = atan2( dble( phantom(1) ), dble( phantom(p+1) ) )
310  c = cos( theta(i) )
311  s = sin( theta(i) )
312  phantom(1) = one
313  phantom(p+1) = one
314  CALL zlarf( 'L', p, q, phantom(1), 1, dconjg(taup1(1)), x11,
315  $ ldx11, work(ilarf) )
316  CALL zlarf( 'L', m-p, q, phantom(p+1), 1, dconjg(taup2(1)),
317  $ x21, ldx21, work(ilarf) )
318  ELSE
319  CALL zunbdb5( p-i+1, m-p-i+1, q-i+1, x11(i,i-1), 1,
320  $ x21(i,i-1), 1, x11(i,i), ldx11, x21(i,i),
321  $ ldx21, work(iorbdb5), lorbdb5, childinfo )
322  CALL zscal( p-i+1, negone, x11(i,i-1), 1 )
323  CALL zlarfgp( p-i+1, x11(i,i-1), x11(i+1,i-1), 1, taup1(i) )
324  CALL zlarfgp( m-p-i+1, x21(i,i-1), x21(i+1,i-1), 1,
325  $ taup2(i) )
326  theta(i) = atan2( dble( x11(i,i-1) ), dble( x21(i,i-1) ) )
327  c = cos( theta(i) )
328  s = sin( theta(i) )
329  x11(i,i-1) = one
330  x21(i,i-1) = one
331  CALL zlarf( 'L', p-i+1, q-i+1, x11(i,i-1), 1,
332  $ dconjg(taup1(i)), x11(i,i), ldx11, work(ilarf) )
333  CALL zlarf( 'L', m-p-i+1, q-i+1, x21(i,i-1), 1,
334  $ dconjg(taup2(i)), x21(i,i), ldx21, work(ilarf) )
335  END IF
336 *
337  CALL zdrot( q-i+1, x11(i,i), ldx11, x21(i,i), ldx21, s, -c )
338  CALL zlacgv( q-i+1, x21(i,i), ldx21 )
339  CALL zlarfgp( q-i+1, x21(i,i), x21(i,i+1), ldx21, tauq1(i) )
340  c = dble( x21(i,i) )
341  x21(i,i) = one
342  CALL zlarf( 'R', p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
343  $ x11(i+1,i), ldx11, work(ilarf) )
344  CALL zlarf( 'R', m-p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
345  $ x21(i+1,i), ldx21, work(ilarf) )
346  CALL zlacgv( q-i+1, x21(i,i), ldx21 )
347  IF( i .LT. m-q ) THEN
348  s = sqrt( dznrm2( p-i, x11(i+1,i), 1 )**2
349  $ + dznrm2( m-p-i, x21(i+1,i), 1 )**2 )
350  phi(i) = atan2( s, c )
351  END IF
352 *
353  END DO
354 *
355 * Reduce the bottom-right portion of X11 to [ I 0 ]
356 *
357  DO i = m - q + 1, p
358  CALL zlacgv( q-i+1, x11(i,i), ldx11 )
359  CALL zlarfgp( q-i+1, x11(i,i), x11(i,i+1), ldx11, tauq1(i) )
360  x11(i,i) = one
361  CALL zlarf( 'R', p-i, q-i+1, x11(i,i), ldx11, tauq1(i),
362  $ x11(i+1,i), ldx11, work(ilarf) )
363  CALL zlarf( 'R', q-p, q-i+1, x11(i,i), ldx11, tauq1(i),
364  $ x21(m-q+1,i), ldx21, work(ilarf) )
365  CALL zlacgv( q-i+1, x11(i,i), ldx11 )
366  END DO
367 *
368 * Reduce the bottom-right portion of X21 to [ 0 I ]
369 *
370  DO i = p + 1, q
371  CALL zlacgv( q-i+1, x21(m-q+i-p,i), ldx21 )
372  CALL zlarfgp( q-i+1, x21(m-q+i-p,i), x21(m-q+i-p,i+1), ldx21,
373  $ tauq1(i) )
374  x21(m-q+i-p,i) = one
375  CALL zlarf( 'R', q-i, q-i+1, x21(m-q+i-p,i), ldx21, tauq1(i),
376  $ x21(m-q+i-p+1,i), ldx21, work(ilarf) )
377  CALL zlacgv( q-i+1, x21(m-q+i-p,i), ldx21 )
378  END DO
379 *
380  RETURN
381 *
382 * End of ZUNBDB4
383 *
384  END
385 
zlacgv
subroutine zlacgv(N, X, INCX)
ZLACGV conjugates a complex vector.
Definition: zlacgv.f:76
zlarf
subroutine zlarf(SIDE, M, N, V, INCV, TAU, C, LDC, WORK)
ZLARF applies an elementary reflector to a general rectangular matrix.
Definition: zlarf.f:130
xerbla
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
zunbdb5
subroutine zunbdb5(M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2, LDQ2, WORK, LWORK, INFO)
ZUNBDB5
Definition: zunbdb5.f:158
zlarfgp
subroutine zlarfgp(N, ALPHA, X, INCX, TAU)
ZLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.
Definition: zlarfgp.f:106
zscal
subroutine zscal(N, ZA, ZX, INCX)
ZSCAL
Definition: zscal.f:80
zunbdb4
subroutine zunbdb4(M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI, TAUP1, TAUP2, TAUQ1, PHANTOM, WORK, LWORK, INFO)
ZUNBDB4
Definition: zunbdb4.f:215
zdrot
subroutine zdrot(N, CX, INCX, CY, INCY, C, S)
ZDROT
Definition: zdrot.f:100