200 SUBROUTINE cunbdb1( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
201 $ TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO )
208 INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
211 REAL PHI(*), THETA(*)
212 COMPLEX TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
213 $ x11(ldx11,*), x21(ldx21,*)
220 parameter( one = (1.0e0,0.0e0) )
224 INTEGER CHILDINFO, I, ILARF, IORBDB5, LLARF, LORBDB5,
233 REAL SCNRM2, SROUNDUP_LWORK
234 EXTERNAL scnrm2, sroundup_lwork
237 INTRINSIC atan2, cos, max, sin, sqrt
244 lquery = lwork .EQ. -1
248 ELSE IF( p .LT. q .OR. m-p .LT. q )
THEN
250 ELSE IF( q .LT. 0 .OR. m-q .LT. q )
THEN
252 ELSE IF( ldx11 .LT. max( 1, p ) )
THEN
254 ELSE IF( ldx21 .LT. max( 1, m-p ) )
THEN
260 IF( info .EQ. 0 )
THEN
262 llarf = max( p-1, m-p-1, q-1 )
265 lworkopt = max( ilarf+llarf-1, iorbdb5+lorbdb5-1 )
267 work(1) = sroundup_lwork(lworkopt)
268 IF( lwork .LT. lworkmin .AND. .NOT.lquery )
THEN
272 IF( info .NE. 0 )
THEN
273 CALL xerbla(
'CUNBDB1', -info )
275 ELSE IF( lquery )
THEN
283 CALL clarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
284 CALL clarfgp( m-p-i+1, x21(i,i), x21(i+1,i), 1, taup2(i) )
285 theta(i) = atan2( real( x21(i,i) ), real( x11(i,i) ) )
290 CALL clarf(
'L', p-i+1, q-i, x11(i,i), 1, conjg(taup1(i)),
291 $ x11(i,i+1), ldx11, work(ilarf) )
292 CALL clarf(
'L', m-p-i+1, q-i, x21(i,i), 1, conjg(taup2(i)),
293 $ x21(i,i+1), ldx21, work(ilarf) )
296 CALL csrot( q-i, x11(i,i+1), ldx11, x21(i,i+1), ldx21, c,
298 CALL clacgv( q-i, x21(i,i+1), ldx21 )
299 CALL clarfgp( q-i, x21(i,i+1), x21(i,i+2), ldx21, tauq1(i) )
300 s = real( x21(i,i+1) )
302 CALL clarf(
'R', p-i, q-i, x21(i,i+1), ldx21, tauq1(i),
303 $ x11(i+1,i+1), ldx11, work(ilarf) )
304 CALL clarf(
'R', m-p-i, q-i, x21(i,i+1), ldx21, tauq1(i),
305 $ x21(i+1,i+1), ldx21, work(ilarf) )
306 CALL clacgv( q-i, x21(i,i+1), ldx21 )
307 c = sqrt( scnrm2( p-i, x11(i+1,i+1), 1 )**2
308 $ + scnrm2( m-p-i, x21(i+1,i+1), 1 )**2 )
309 phi(i) = atan2( s, c )
310 CALL cunbdb5( p-i, m-p-i, q-i-1, x11(i+1,i+1), 1,
311 $ x21(i+1,i+1), 1, x11(i+1,i+2), ldx11,
312 $ x21(i+1,i+2), ldx21, work(iorbdb5), lorbdb5,
subroutine xerbla(srname, info)
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
subroutine clarf(side, m, n, v, incv, tau, c, ldc, work)
CLARF applies an elementary reflector to a general rectangular matrix.
subroutine clarfgp(n, alpha, x, incx, tau)
CLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.
subroutine csrot(n, cx, incx, cy, incy, c, s)
CSROT
subroutine cunbdb1(m, p, q, x11, ldx11, x21, ldx21, theta, phi, taup1, taup2, tauq1, work, lwork, info)
CUNBDB1
subroutine cunbdb5(m1, m2, n, x1, incx1, x2, incx2, q1, ldq1, q2, ldq2, work, lwork, info)
CUNBDB5