200 SUBROUTINE sorbdb3( 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 REAL TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
213 $ x11(ldx11,*), x21(ldx21,*)
220 parameter( one = 1.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(
'SORBDB3', -info )
274 ELSE IF( lquery )
THEN
283 CALL srot( q-i+1, x11(i-1,i), ldx11, x21(i,i), ldx11, c, s )
286 CALL slarfgp( q-i+1, x21(i,i), x21(i,i+1), ldx21, tauq1(i) )
289 CALL slarf(
'R', p-i+1, q-i+1, x21(i,i), ldx21, tauq1(i),
290 $ x11(i,i), ldx11, work(ilarf) )
291 CALL slarf(
'R', m-p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
292 $ x21(i+1,i), ldx21, work(ilarf) )
293 c = sqrt( snrm2( p-i+1, x11(i,i), 1 )**2
294 $ + snrm2( m-p-i, x21(i+1,i), 1 )**2 )
295 theta(i) = atan2( s, c )
297 CALL sorbdb5( p-i+1, m-p-i, q-i, x11(i,i), 1, x21(i+1,i), 1,
298 $ x11(i,i+1), ldx11, x21(i+1,i+1), ldx21,
299 $ work(iorbdb5), lorbdb5, childinfo )
300 CALL slarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
301 IF( i .LT. m-p )
THEN
302 CALL slarfgp( m-p-i, x21(i+1,i), x21(i+2,i), 1, taup2(i) )
303 phi(i) = atan2( x21(i+1,i), x11(i,i) )
307 CALL slarf(
'L', m-p-i, q-i, x21(i+1,i), 1, taup2(i),
308 $ x21(i+1,i+1), ldx21, work(ilarf) )
311 CALL slarf(
'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,i+1),
312 $ ldx11, work(ilarf) )
319 CALL slarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
321 CALL slarf(
'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,i+1),
322 $ ldx11, work(ilarf) )
subroutine xerbla(srname, info)
subroutine slarf(side, m, n, v, incv, tau, c, ldc, work)
SLARF applies an elementary reflector to a general rectangular matrix.
subroutine slarfgp(n, alpha, x, incx, tau)
SLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.
subroutine srot(n, sx, incx, sy, incy, c, s)
SROT
subroutine sorbdb3(m, p, q, x11, ldx11, x21, ldx21, theta, phi, taup1, taup2, tauq1, work, lwork, info)
SORBDB3
subroutine sorbdb5(m1, m2, n, x1, incx1, x2, incx2, q1, ldq1, q2, ldq2, work, lwork, info)
SORBDB5