LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zunbdb.f
Go to the documentation of this file.
1 *> \brief \b ZUNBDB
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download ZUNBDB + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunbdb.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunbdb.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunbdb.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZUNBDB( TRANS, SIGNS, M, P, Q, X11, LDX11, X12, LDX12,
22 * X21, LDX21, X22, LDX22, THETA, PHI, TAUP1,
23 * TAUP2, TAUQ1, TAUQ2, WORK, LWORK, INFO )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER SIGNS, TRANS
27 * INTEGER INFO, LDX11, LDX12, LDX21, LDX22, LWORK, M, P,
28 * $ Q
29 * ..
30 * .. Array Arguments ..
31 * DOUBLE PRECISION PHI( * ), THETA( * )
32 * COMPLEX*16 TAUP1( * ), TAUP2( * ), TAUQ1( * ), TAUQ2( * ),
33 * $ WORK( * ), X11( LDX11, * ), X12( LDX12, * ),
34 * $ X21( LDX21, * ), X22( LDX22, * )
35 * ..
36 *
37 *
38 *> \par Purpose:
39 * =============
40 *>
41 *> \verbatim
42 *>
43 *> ZUNBDB simultaneously bidiagonalizes the blocks of an M-by-M
44 *> partitioned unitary matrix X:
45 *>
46 *> [ B11 | B12 0 0 ]
47 *> [ X11 | X12 ] [ P1 | ] [ 0 | 0 -I 0 ] [ Q1 | ]**H
48 *> X = [-----------] = [---------] [----------------] [---------] .
49 *> [ X21 | X22 ] [ | P2 ] [ B21 | B22 0 0 ] [ | Q2 ]
50 *> [ 0 | 0 0 I ]
51 *>
52 *> X11 is P-by-Q. Q must be no larger than P, M-P, or M-Q. (If this is
53 *> not the case, then X must be transposed and/or permuted. This can be
54 *> done in constant time using the TRANS and SIGNS options. See ZUNCSD
55 *> for details.)
56 *>
57 *> The unitary matrices P1, P2, Q1, and Q2 are P-by-P, (M-P)-by-
58 *> (M-P), Q-by-Q, and (M-Q)-by-(M-Q), respectively. They are
59 *> represented implicitly by Householder vectors.
60 *>
61 *> B11, B12, B21, and B22 are Q-by-Q bidiagonal matrices represented
62 *> implicitly by angles THETA, PHI.
63 *> \endverbatim
64 *
65 * Arguments:
66 * ==========
67 *
68 *> \param[in] TRANS
69 *> \verbatim
70 *> TRANS is CHARACTER
71 *> = 'T': X, U1, U2, V1T, and V2T are stored in row-major
72 *> order;
73 *> otherwise: X, U1, U2, V1T, and V2T are stored in column-
74 *> major order.
75 *> \endverbatim
76 *>
77 *> \param[in] SIGNS
78 *> \verbatim
79 *> SIGNS is CHARACTER
80 *> = 'O': The lower-left block is made nonpositive (the
81 *> "other" convention);
82 *> otherwise: The upper-right block is made nonpositive (the
83 *> "default" convention).
84 *> \endverbatim
85 *>
86 *> \param[in] M
87 *> \verbatim
88 *> M is INTEGER
89 *> The number of rows and columns in X.
90 *> \endverbatim
91 *>
92 *> \param[in] P
93 *> \verbatim
94 *> P is INTEGER
95 *> The number of rows in X11 and X12. 0 <= P <= M.
96 *> \endverbatim
97 *>
98 *> \param[in] Q
99 *> \verbatim
100 *> Q is INTEGER
101 *> The number of columns in X11 and X21. 0 <= Q <=
102 *> MIN(P,M-P,M-Q).
103 *> \endverbatim
104 *>
105 *> \param[in,out] X11
106 *> \verbatim
107 *> X11 is COMPLEX*16 array, dimension (LDX11,Q)
108 *> On entry, the top-left block of the unitary matrix to be
109 *> reduced. On exit, the form depends on TRANS:
110 *> If TRANS = 'N', then
111 *> the columns of tril(X11) specify reflectors for P1,
112 *> the rows of triu(X11,1) specify reflectors for Q1;
113 *> else TRANS = 'T', and
114 *> the rows of triu(X11) specify reflectors for P1,
115 *> the columns of tril(X11,-1) specify reflectors for Q1.
116 *> \endverbatim
117 *>
118 *> \param[in] LDX11
119 *> \verbatim
120 *> LDX11 is INTEGER
121 *> The leading dimension of X11. If TRANS = 'N', then LDX11 >=
122 *> P; else LDX11 >= Q.
123 *> \endverbatim
124 *>
125 *> \param[in,out] X12
126 *> \verbatim
127 *> X12 is COMPLEX*16 array, dimension (LDX12,M-Q)
128 *> On entry, the top-right block of the unitary matrix to
129 *> be reduced. On exit, the form depends on TRANS:
130 *> If TRANS = 'N', then
131 *> the rows of triu(X12) specify the first P reflectors for
132 *> Q2;
133 *> else TRANS = 'T', and
134 *> the columns of tril(X12) specify the first P reflectors
135 *> for Q2.
136 *> \endverbatim
137 *>
138 *> \param[in] LDX12
139 *> \verbatim
140 *> LDX12 is INTEGER
141 *> The leading dimension of X12. If TRANS = 'N', then LDX12 >=
142 *> P; else LDX11 >= M-Q.
143 *> \endverbatim
144 *>
145 *> \param[in,out] X21
146 *> \verbatim
147 *> X21 is COMPLEX*16 array, dimension (LDX21,Q)
148 *> On entry, the bottom-left block of the unitary matrix to
149 *> be reduced. On exit, the form depends on TRANS:
150 *> If TRANS = 'N', then
151 *> the columns of tril(X21) specify reflectors for P2;
152 *> else TRANS = 'T', and
153 *> the rows of triu(X21) specify reflectors for P2.
154 *> \endverbatim
155 *>
156 *> \param[in] LDX21
157 *> \verbatim
158 *> LDX21 is INTEGER
159 *> The leading dimension of X21. If TRANS = 'N', then LDX21 >=
160 *> M-P; else LDX21 >= Q.
161 *> \endverbatim
162 *>
163 *> \param[in,out] X22
164 *> \verbatim
165 *> X22 is COMPLEX*16 array, dimension (LDX22,M-Q)
166 *> On entry, the bottom-right block of the unitary matrix to
167 *> be reduced. On exit, the form depends on TRANS:
168 *> If TRANS = 'N', then
169 *> the rows of triu(X22(Q+1:M-P,P+1:M-Q)) specify the last
170 *> M-P-Q reflectors for Q2,
171 *> else TRANS = 'T', and
172 *> the columns of tril(X22(P+1:M-Q,Q+1:M-P)) specify the last
173 *> M-P-Q reflectors for P2.
174 *> \endverbatim
175 *>
176 *> \param[in] LDX22
177 *> \verbatim
178 *> LDX22 is INTEGER
179 *> The leading dimension of X22. If TRANS = 'N', then LDX22 >=
180 *> M-P; else LDX22 >= M-Q.
181 *> \endverbatim
182 *>
183 *> \param[out] THETA
184 *> \verbatim
185 *> THETA is DOUBLE PRECISION array, dimension (Q)
186 *> The entries of the bidiagonal blocks B11, B12, B21, B22 can
187 *> be computed from the angles THETA and PHI. See Further
188 *> Details.
189 *> \endverbatim
190 *>
191 *> \param[out] PHI
192 *> \verbatim
193 *> PHI is DOUBLE PRECISION array, dimension (Q-1)
194 *> The entries of the bidiagonal blocks B11, B12, B21, B22 can
195 *> be computed from the angles THETA and PHI. See Further
196 *> Details.
197 *> \endverbatim
198 *>
199 *> \param[out] TAUP1
200 *> \verbatim
201 *> TAUP1 is COMPLEX*16 array, dimension (P)
202 *> The scalar factors of the elementary reflectors that define
203 *> P1.
204 *> \endverbatim
205 *>
206 *> \param[out] TAUP2
207 *> \verbatim
208 *> TAUP2 is COMPLEX*16 array, dimension (M-P)
209 *> The scalar factors of the elementary reflectors that define
210 *> P2.
211 *> \endverbatim
212 *>
213 *> \param[out] TAUQ1
214 *> \verbatim
215 *> TAUQ1 is COMPLEX*16 array, dimension (Q)
216 *> The scalar factors of the elementary reflectors that define
217 *> Q1.
218 *> \endverbatim
219 *>
220 *> \param[out] TAUQ2
221 *> \verbatim
222 *> TAUQ2 is COMPLEX*16 array, dimension (M-Q)
223 *> The scalar factors of the elementary reflectors that define
224 *> Q2.
225 *> \endverbatim
226 *>
227 *> \param[out] WORK
228 *> \verbatim
229 *> WORK is COMPLEX*16 array, dimension (LWORK)
230 *> \endverbatim
231 *>
232 *> \param[in] LWORK
233 *> \verbatim
234 *> LWORK is INTEGER
235 *> The dimension of the array WORK. LWORK >= M-Q.
236 *>
237 *> If LWORK = -1, then a workspace query is assumed; the routine
238 *> only calculates the optimal size of the WORK array, returns
239 *> this value as the first entry of the WORK array, and no error
240 *> message related to LWORK is issued by XERBLA.
241 *> \endverbatim
242 *>
243 *> \param[out] INFO
244 *> \verbatim
245 *> INFO is INTEGER
246 *> = 0: successful exit.
247 *> < 0: if INFO = -i, the i-th argument had an illegal value.
248 *> \endverbatim
249 *
250 * Authors:
251 * ========
252 *
253 *> \author Univ. of Tennessee
254 *> \author Univ. of California Berkeley
255 *> \author Univ. of Colorado Denver
256 *> \author NAG Ltd.
257 *
258 *> \date November 2011
259 *
260 *> \ingroup complex16OTHERcomputational
261 *
262 *> \par Further Details:
263 * =====================
264 *>
265 *> \verbatim
266 *>
267 *> The bidiagonal blocks B11, B12, B21, and B22 are represented
268 *> implicitly by angles THETA(1), ..., THETA(Q) and PHI(1), ...,
269 *> PHI(Q-1). B11 and B21 are upper bidiagonal, while B21 and B22 are
270 *> lower bidiagonal. Every entry in each bidiagonal band is a product
271 *> of a sine or cosine of a THETA with a sine or cosine of a PHI. See
272 *> [1] or ZUNCSD for details.
273 *>
274 *> P1, P2, Q1, and Q2 are represented as products of elementary
275 *> reflectors. See ZUNCSD for details on generating P1, P2, Q1, and Q2
276 *> using ZUNGQR and ZUNGLQ.
277 *> \endverbatim
278 *
279 *> \par References:
280 * ================
281 *>
282 *> [1] Brian D. Sutton. Computing the complete CS decomposition. Numer.
283 *> Algorithms, 50(1):33-65, 2009.
284 *>
285 * =====================================================================
286  SUBROUTINE zunbdb( TRANS, SIGNS, M, P, Q, X11, LDX11, X12, LDX12,
287  $ x21, ldx21, x22, ldx22, theta, phi, taup1,
288  $ taup2, tauq1, tauq2, work, lwork, info )
289 *
290 * -- LAPACK computational routine (version 3.4.0) --
291 * -- LAPACK is a software package provided by Univ. of Tennessee, --
292 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
293 * November 2011
294 *
295 * .. Scalar Arguments ..
296  CHARACTER signs, trans
297  INTEGER info, ldx11, ldx12, ldx21, ldx22, lwork, m, p,
298  $ q
299 * ..
300 * .. Array Arguments ..
301  DOUBLE PRECISION phi( * ), theta( * )
302  COMPLEX*16 taup1( * ), taup2( * ), tauq1( * ), tauq2( * ),
303  $ work( * ), x11( ldx11, * ), x12( ldx12, * ),
304  $ x21( ldx21, * ), x22( ldx22, * )
305 * ..
306 *
307 * ====================================================================
308 *
309 * .. Parameters ..
310  DOUBLE PRECISION realone
311  parameter( realone = 1.0d0 )
312  COMPLEX*16 one
313  parameter( one = (1.0d0,0.0d0) )
314 * ..
315 * .. Local Scalars ..
316  LOGICAL colmajor, lquery
317  INTEGER i, lworkmin, lworkopt
318  DOUBLE PRECISION z1, z2, z3, z4
319 * ..
320 * .. External Subroutines ..
321  EXTERNAL zaxpy, zlarf, zlarfgp, zscal, xerbla
322  EXTERNAL zlacgv
323 *
324 * ..
325 * .. External Functions ..
326  DOUBLE PRECISION dznrm2
327  LOGICAL lsame
328  EXTERNAL dznrm2, lsame
329 * ..
330 * .. Intrinsic Functions
331  INTRINSIC atan2, cos, max, min, sin
332  INTRINSIC dcmplx, dconjg
333 * ..
334 * .. Executable Statements ..
335 *
336 * Test input arguments
337 *
338  info = 0
339  colmajor = .NOT. lsame( trans, 'T' )
340  IF( .NOT. lsame( signs, 'O' ) ) THEN
341  z1 = realone
342  z2 = realone
343  z3 = realone
344  z4 = realone
345  ELSE
346  z1 = realone
347  z2 = -realone
348  z3 = realone
349  z4 = -realone
350  END IF
351  lquery = lwork .EQ. -1
352 *
353  IF( m .LT. 0 ) THEN
354  info = -3
355  ELSE IF( p .LT. 0 .OR. p .GT. m ) THEN
356  info = -4
357  ELSE IF( q .LT. 0 .OR. q .GT. p .OR. q .GT. m-p .OR.
358  $ q .GT. m-q ) THEN
359  info = -5
360  ELSE IF( colmajor .AND. ldx11 .LT. max( 1, p ) ) THEN
361  info = -7
362  ELSE IF( .NOT.colmajor .AND. ldx11 .LT. max( 1, q ) ) THEN
363  info = -7
364  ELSE IF( colmajor .AND. ldx12 .LT. max( 1, p ) ) THEN
365  info = -9
366  ELSE IF( .NOT.colmajor .AND. ldx12 .LT. max( 1, m-q ) ) THEN
367  info = -9
368  ELSE IF( colmajor .AND. ldx21 .LT. max( 1, m-p ) ) THEN
369  info = -11
370  ELSE IF( .NOT.colmajor .AND. ldx21 .LT. max( 1, q ) ) THEN
371  info = -11
372  ELSE IF( colmajor .AND. ldx22 .LT. max( 1, m-p ) ) THEN
373  info = -13
374  ELSE IF( .NOT.colmajor .AND. ldx22 .LT. max( 1, m-q ) ) THEN
375  info = -13
376  END IF
377 *
378 * Compute workspace
379 *
380  IF( info .EQ. 0 ) THEN
381  lworkopt = m - q
382  lworkmin = m - q
383  work(1) = lworkopt
384  IF( lwork .LT. lworkmin .AND. .NOT. lquery ) THEN
385  info = -21
386  END IF
387  END IF
388  IF( info .NE. 0 ) THEN
389  CALL xerbla( 'xORBDB', -info )
390  return
391  ELSE IF( lquery ) THEN
392  return
393  END IF
394 *
395 * Handle column-major and row-major separately
396 *
397  IF( colmajor ) THEN
398 *
399 * Reduce columns 1, ..., Q of X11, X12, X21, and X22
400 *
401  DO i = 1, q
402 *
403  IF( i .EQ. 1 ) THEN
404  CALL zscal( p-i+1, dcmplx( z1, 0.0d0 ), x11(i,i), 1 )
405  ELSE
406  CALL zscal( p-i+1, dcmplx( z1*cos(phi(i-1)), 0.0d0 ),
407  $ x11(i,i), 1 )
408  CALL zaxpy( p-i+1, dcmplx( -z1*z3*z4*sin(phi(i-1)),
409  $ 0.0d0 ), x12(i,i-1), 1, x11(i,i), 1 )
410  END IF
411  IF( i .EQ. 1 ) THEN
412  CALL zscal( m-p-i+1, dcmplx( z2, 0.0d0 ), x21(i,i), 1 )
413  ELSE
414  CALL zscal( m-p-i+1, dcmplx( z2*cos(phi(i-1)), 0.0d0 ),
415  $ x21(i,i), 1 )
416  CALL zaxpy( m-p-i+1, dcmplx( -z2*z3*z4*sin(phi(i-1)),
417  $ 0.0d0 ), x22(i,i-1), 1, x21(i,i), 1 )
418  END IF
419 *
420  theta(i) = atan2( dznrm2( m-p-i+1, x21(i,i), 1 ),
421  $ dznrm2( p-i+1, x11(i,i), 1 ) )
422 *
423  CALL zlarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
424  x11(i,i) = one
425  CALL zlarfgp( m-p-i+1, x21(i,i), x21(i+1,i), 1, taup2(i) )
426  x21(i,i) = one
427 *
428  CALL zlarf( 'L', p-i+1, q-i, x11(i,i), 1, dconjg(taup1(i)),
429  $ x11(i,i+1), ldx11, work )
430  CALL zlarf( 'L', p-i+1, m-q-i+1, x11(i,i), 1,
431  $ dconjg(taup1(i)), x12(i,i), ldx12, work )
432  CALL zlarf( 'L', m-p-i+1, q-i, x21(i,i), 1,
433  $ dconjg(taup2(i)), x21(i,i+1), ldx21, work )
434  CALL zlarf( 'L', m-p-i+1, m-q-i+1, x21(i,i), 1,
435  $ dconjg(taup2(i)), x22(i,i), ldx22, work )
436 *
437  IF( i .LT. q ) THEN
438  CALL zscal( q-i, dcmplx( -z1*z3*sin(theta(i)), 0.0d0 ),
439  $ x11(i,i+1), ldx11 )
440  CALL zaxpy( q-i, dcmplx( z2*z3*cos(theta(i)), 0.0d0 ),
441  $ x21(i,i+1), ldx21, x11(i,i+1), ldx11 )
442  END IF
443  CALL zscal( m-q-i+1, dcmplx( -z1*z4*sin(theta(i)), 0.0d0 ),
444  $ x12(i,i), ldx12 )
445  CALL zaxpy( m-q-i+1, dcmplx( z2*z4*cos(theta(i)), 0.0d0 ),
446  $ x22(i,i), ldx22, x12(i,i), ldx12 )
447 *
448  IF( i .LT. q )
449  $ phi(i) = atan2( dznrm2( q-i, x11(i,i+1), ldx11 ),
450  $ dznrm2( m-q-i+1, x12(i,i), ldx12 ) )
451 *
452  IF( i .LT. q ) THEN
453  CALL zlacgv( q-i, x11(i,i+1), ldx11 )
454  CALL zlarfgp( q-i, x11(i,i+1), x11(i,i+2), ldx11,
455  $ tauq1(i) )
456  x11(i,i+1) = one
457  END IF
458  CALL zlacgv( m-q-i+1, x12(i,i), ldx12 )
459  CALL zlarfgp( m-q-i+1, x12(i,i), x12(i,i+1), ldx12,
460  $ tauq2(i) )
461  x12(i,i) = one
462 *
463  IF( i .LT. q ) THEN
464  CALL zlarf( 'R', p-i, q-i, x11(i,i+1), ldx11, tauq1(i),
465  $ x11(i+1,i+1), ldx11, work )
466  CALL zlarf( 'R', m-p-i, q-i, x11(i,i+1), ldx11, tauq1(i),
467  $ x21(i+1,i+1), ldx21, work )
468  END IF
469  CALL zlarf( 'R', p-i, m-q-i+1, x12(i,i), ldx12, tauq2(i),
470  $ x12(i+1,i), ldx12, work )
471  CALL zlarf( 'R', m-p-i, m-q-i+1, x12(i,i), ldx12, tauq2(i),
472  $ x22(i+1,i), ldx22, work )
473 *
474  IF( i .LT. q )
475  $ CALL zlacgv( q-i, x11(i,i+1), ldx11 )
476  CALL zlacgv( m-q-i+1, x12(i,i), ldx12 )
477 *
478  END DO
479 *
480 * Reduce columns Q + 1, ..., P of X12, X22
481 *
482  DO i = q + 1, p
483 *
484  CALL zscal( m-q-i+1, dcmplx( -z1*z4, 0.0d0 ), x12(i,i),
485  $ ldx12 )
486  CALL zlacgv( m-q-i+1, x12(i,i), ldx12 )
487  CALL zlarfgp( m-q-i+1, x12(i,i), x12(i,i+1), ldx12,
488  $ tauq2(i) )
489  x12(i,i) = one
490 *
491  CALL zlarf( 'R', p-i, m-q-i+1, x12(i,i), ldx12, tauq2(i),
492  $ x12(i+1,i), ldx12, work )
493  IF( m-p-q .GE. 1 )
494  $ CALL zlarf( 'R', m-p-q, m-q-i+1, x12(i,i), ldx12,
495  $ tauq2(i), x22(q+1,i), ldx22, work )
496 *
497  CALL zlacgv( m-q-i+1, x12(i,i), ldx12 )
498 *
499  END DO
500 *
501 * Reduce columns P + 1, ..., M - Q of X12, X22
502 *
503  DO i = 1, m - p - q
504 *
505  CALL zscal( m-p-q-i+1, dcmplx( z2*z4, 0.0d0 ),
506  $ x22(q+i,p+i), ldx22 )
507  CALL zlacgv( m-p-q-i+1, x22(q+i,p+i), ldx22 )
508  CALL zlarfgp( m-p-q-i+1, x22(q+i,p+i), x22(q+i,p+i+1),
509  $ ldx22, tauq2(p+i) )
510  x22(q+i,p+i) = one
511  CALL zlarf( 'R', m-p-q-i, m-p-q-i+1, x22(q+i,p+i), ldx22,
512  $ tauq2(p+i), x22(q+i+1,p+i), ldx22, work )
513 *
514  CALL zlacgv( m-p-q-i+1, x22(q+i,p+i), ldx22 )
515 *
516  END DO
517 *
518  ELSE
519 *
520 * Reduce columns 1, ..., Q of X11, X12, X21, X22
521 *
522  DO i = 1, q
523 *
524  IF( i .EQ. 1 ) THEN
525  CALL zscal( p-i+1, dcmplx( z1, 0.0d0 ), x11(i,i),
526  $ ldx11 )
527  ELSE
528  CALL zscal( p-i+1, dcmplx( z1*cos(phi(i-1)), 0.0d0 ),
529  $ x11(i,i), ldx11 )
530  CALL zaxpy( p-i+1, dcmplx( -z1*z3*z4*sin(phi(i-1)),
531  $ 0.0d0 ), x12(i-1,i), ldx12, x11(i,i), ldx11 )
532  END IF
533  IF( i .EQ. 1 ) THEN
534  CALL zscal( m-p-i+1, dcmplx( z2, 0.0d0 ), x21(i,i),
535  $ ldx21 )
536  ELSE
537  CALL zscal( m-p-i+1, dcmplx( z2*cos(phi(i-1)), 0.0d0 ),
538  $ x21(i,i), ldx21 )
539  CALL zaxpy( m-p-i+1, dcmplx( -z2*z3*z4*sin(phi(i-1)),
540  $ 0.0d0 ), x22(i-1,i), ldx22, x21(i,i), ldx21 )
541  END IF
542 *
543  theta(i) = atan2( dznrm2( m-p-i+1, x21(i,i), ldx21 ),
544  $ dznrm2( p-i+1, x11(i,i), ldx11 ) )
545 *
546  CALL zlacgv( p-i+1, x11(i,i), ldx11 )
547  CALL zlacgv( m-p-i+1, x21(i,i), ldx21 )
548 *
549  CALL zlarfgp( p-i+1, x11(i,i), x11(i,i+1), ldx11, taup1(i) )
550  x11(i,i) = one
551  CALL zlarfgp( m-p-i+1, x21(i,i), x21(i,i+1), ldx21,
552  $ taup2(i) )
553  x21(i,i) = one
554 *
555  CALL zlarf( 'R', q-i, p-i+1, x11(i,i), ldx11, taup1(i),
556  $ x11(i+1,i), ldx11, work )
557  CALL zlarf( 'R', m-q-i+1, p-i+1, x11(i,i), ldx11, taup1(i),
558  $ x12(i,i), ldx12, work )
559  CALL zlarf( 'R', q-i, m-p-i+1, x21(i,i), ldx21, taup2(i),
560  $ x21(i+1,i), ldx21, work )
561  CALL zlarf( 'R', m-q-i+1, m-p-i+1, x21(i,i), ldx21,
562  $ taup2(i), x22(i,i), ldx22, work )
563 *
564  CALL zlacgv( p-i+1, x11(i,i), ldx11 )
565  CALL zlacgv( m-p-i+1, x21(i,i), ldx21 )
566 *
567  IF( i .LT. q ) THEN
568  CALL zscal( q-i, dcmplx( -z1*z3*sin(theta(i)), 0.0d0 ),
569  $ x11(i+1,i), 1 )
570  CALL zaxpy( q-i, dcmplx( z2*z3*cos(theta(i)), 0.0d0 ),
571  $ x21(i+1,i), 1, x11(i+1,i), 1 )
572  END IF
573  CALL zscal( m-q-i+1, dcmplx( -z1*z4*sin(theta(i)), 0.0d0 ),
574  $ x12(i,i), 1 )
575  CALL zaxpy( m-q-i+1, dcmplx( z2*z4*cos(theta(i)), 0.0d0 ),
576  $ x22(i,i), 1, x12(i,i), 1 )
577 *
578  IF( i .LT. q )
579  $ phi(i) = atan2( dznrm2( q-i, x11(i+1,i), 1 ),
580  $ dznrm2( m-q-i+1, x12(i,i), 1 ) )
581 *
582  IF( i .LT. q ) THEN
583  CALL zlarfgp( q-i, x11(i+1,i), x11(i+2,i), 1, tauq1(i) )
584  x11(i+1,i) = one
585  END IF
586  CALL zlarfgp( m-q-i+1, x12(i,i), x12(i+1,i), 1, tauq2(i) )
587  x12(i,i) = one
588 *
589  IF( i .LT. q ) THEN
590  CALL zlarf( 'L', q-i, p-i, x11(i+1,i), 1,
591  $ dconjg(tauq1(i)), x11(i+1,i+1), ldx11, work )
592  CALL zlarf( 'L', q-i, m-p-i, x11(i+1,i), 1,
593  $ dconjg(tauq1(i)), x21(i+1,i+1), ldx21, work )
594  END IF
595  CALL zlarf( 'L', m-q-i+1, p-i, x12(i,i), 1,
596  $ dconjg(tauq2(i)), x12(i,i+1), ldx12, work )
597  CALL zlarf( 'L', m-q-i+1, m-p-i, x12(i,i), 1,
598  $ dconjg(tauq2(i)), x22(i,i+1), ldx22, work )
599 *
600  END DO
601 *
602 * Reduce columns Q + 1, ..., P of X12, X22
603 *
604  DO i = q + 1, p
605 *
606  CALL zscal( m-q-i+1, dcmplx( -z1*z4, 0.0d0 ), x12(i,i), 1 )
607  CALL zlarfgp( m-q-i+1, x12(i,i), x12(i+1,i), 1, tauq2(i) )
608  x12(i,i) = one
609 *
610  CALL zlarf( 'L', m-q-i+1, p-i, x12(i,i), 1,
611  $ dconjg(tauq2(i)), x12(i,i+1), ldx12, work )
612  IF( m-p-q .GE. 1 )
613  $ CALL zlarf( 'L', m-q-i+1, m-p-q, x12(i,i), 1,
614  $ dconjg(tauq2(i)), x22(i,q+1), ldx22, work )
615 *
616  END DO
617 *
618 * Reduce columns P + 1, ..., M - Q of X12, X22
619 *
620  DO i = 1, m - p - q
621 *
622  CALL zscal( m-p-q-i+1, dcmplx( z2*z4, 0.0d0 ),
623  $ x22(p+i,q+i), 1 )
624  CALL zlarfgp( m-p-q-i+1, x22(p+i,q+i), x22(p+i+1,q+i), 1,
625  $ tauq2(p+i) )
626  x22(p+i,q+i) = one
627 *
628  CALL zlarf( 'L', m-p-q-i+1, m-p-q-i, x22(p+i,q+i), 1,
629  $ dconjg(tauq2(p+i)), x22(p+i,q+i+1), ldx22,
630  $ work )
631 *
632  END DO
633 *
634  END IF
635 *
636  return
637 *
638 * End of ZUNBDB
639 *
640  END
641