200 SUBROUTINE cunbdb3( 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,
236 INTRINSIC atan2, cos, max, sin, sqrt
243 lquery = lwork .EQ. -1
247 ELSE IF( 2*p .LT. m .OR. p .GT. m )
THEN
249 ELSE IF( q .LT. m-p .OR. m-q .LT. m-p )
THEN
251 ELSE IF( ldx11 .LT. max( 1, p ) )
THEN
253 ELSE IF( ldx21 .LT. max( 1, m-p ) )
THEN
259 IF( info .EQ. 0 )
THEN
261 llarf = max( p, m-p-1, q-1 )
264 lworkopt = max( ilarf+llarf-1, iorbdb5+lorbdb5-1 )
267 IF( lwork .LT. lworkmin .AND. .NOT.lquery )
THEN
271 IF( info .NE. 0 )
THEN
272 CALL xerbla(
'CUNBDB3', -info )
274 ELSE IF( lquery )
THEN
283 CALL csrot( q-i+1, x11(i-1,i), ldx11, x21(i,i), ldx11, c,
287 CALL clacgv( q-i+1, x21(i,i), ldx21 )
288 CALL clarfgp( q-i+1, x21(i,i), x21(i,i+1), ldx21, tauq1(i) )
291 CALL clarf(
'R', p-i+1, q-i+1, x21(i,i), ldx21, tauq1(i),
292 $ x11(i,i), ldx11, work(ilarf) )
293 CALL clarf(
'R', m-p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
294 $ x21(i+1,i), ldx21, work(ilarf) )
295 CALL clacgv( q-i+1, x21(i,i), ldx21 )
296 c = sqrt( scnrm2( p-i+1, x11(i,i), 1 )**2
297 $ + scnrm2( m-p-i, x21(i+1,i), 1 )**2 )
298 theta(i) = atan2( s, c )
300 CALL cunbdb5( p-i+1, m-p-i, q-i, x11(i,i), 1, x21(i+1,i), 1,
301 $ x11(i,i+1), ldx11, x21(i+1,i+1), ldx21,
302 $ work(iorbdb5), lorbdb5, childinfo )
303 CALL clarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
304 IF( i .LT. m-p )
THEN
305 CALL clarfgp( m-p-i, x21(i+1,i), x21(i+2,i), 1, taup2(i) )
306 phi(i) = atan2( real( x21(i+1,i) ), real( x11(i,i) ) )
310 CALL clarf(
'L', m-p-i, q-i, x21(i+1,i), 1, conjg(taup2(i)),
311 $ x21(i+1,i+1), ldx21, work(ilarf) )
314 CALL clarf(
'L', p-i+1, q-i, x11(i,i), 1, conjg(taup1(i)),
315 $ x11(i,i+1), ldx11, work(ilarf) )
322 CALL clarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
324 CALL clarf(
'L', p-i+1, q-i, x11(i,i), 1, conjg(taup1(i)),
325 $ x11(i,i+1), ldx11, work(ilarf) )
subroutine xerbla(SRNAME, INFO)
XERBLA
subroutine csrot(N, CX, INCX, CY, INCY, C, S)
CSROT
subroutine clarfgp(N, ALPHA, X, INCX, TAU)
CLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.
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 cunbdb5(M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2, LDQ2, WORK, LWORK, INFO)
CUNBDB5
subroutine cunbdb3(M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI, TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO)
CUNBDB3