201 SUBROUTINE sorbdb1( M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,
202 $ TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO )
209 INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
212 REAL PHI(*), THETA(*)
213 REAL TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
214 $ x11(ldx11,*), x21(ldx21,*)
221 parameter( one = 1.0e0 )
225 INTEGER CHILDINFO, I, ILARF, IORBDB5, LLARF, LORBDB5,
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 )
268 IF( lwork .LT. lworkmin .AND. .NOT.lquery )
THEN
272 IF( info .NE. 0 )
THEN
273 CALL xerbla(
'SORBDB1', -info )
275 ELSE IF( lquery )
THEN
283 CALL slarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
284 CALL slarfgp( m-p-i+1, x21(i,i), x21(i+1,i), 1, taup2(i) )
285 theta(i) = atan2( x21(i,i), x11(i,i) )
290 CALL slarf(
'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,i+1),
291 $ ldx11, work(ilarf) )
292 CALL slarf(
'L', m-p-i+1, q-i, x21(i,i), 1, taup2(i),
293 $ x21(i,i+1), ldx21, work(ilarf) )
296 CALL srot( q-i, x11(i,i+1), ldx11, x21(i,i+1), ldx21, c, s )
297 CALL slarfgp( q-i, x21(i,i+1), x21(i,i+2), ldx21, tauq1(i) )
300 CALL slarf(
'R', p-i, q-i, x21(i,i+1), ldx21, tauq1(i),
301 $ x11(i+1,i+1), ldx11, work(ilarf) )
302 CALL slarf(
'R', m-p-i, q-i, x21(i,i+1), ldx21, tauq1(i),
303 $ x21(i+1,i+1), ldx21, work(ilarf) )
304 c = sqrt( snrm2( p-i, x11(i+1,i+1), 1 )**2
305 $ + snrm2( m-p-i, x21(i+1,i+1), 1 )**2 )
306 phi(i) = atan2( s, c )
307 CALL sorbdb5( p-i, m-p-i, q-i-1, x11(i+1,i+1), 1,
308 $ x21(i+1,i+1), 1, x11(i+1,i+2), ldx11,
309 $ x21(i+1,i+2), ldx21, work(iorbdb5), lorbdb5,
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 sorbdb1(m, p, q, x11, ldx11, x21, ldx21, theta, phi, taup1, taup2, tauq1, work, lwork, info)
SORBDB1
subroutine sorbdb5(m1, m2, n, x1, incx1, x2, incx2, q1, ldq1, q2, ldq2, work, lwork, info)
SORBDB5