LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sorbdb3()

subroutine sorbdb3 ( integer m,
integer p,
integer q,
real, dimension(ldx11,*) x11,
integer ldx11,
real, dimension(ldx21,*) x21,
integer ldx21,
real, dimension(*) theta,
real, dimension(*) phi,
real, dimension(*) taup1,
real, dimension(*) taup2,
real, dimension(*) tauq1,
real, dimension(*) work,
integer lwork,
integer info )

SORBDB3

Download SORBDB3 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> SORBDB3 simultaneously bidiagonalizes the blocks of a tall and skinny
!> matrix X with orthonormal columns:
!>
!>                            [ B11 ]
!>      [ X11 ]   [ P1 |    ] [  0  ]
!>      [-----] = [---------] [-----] Q1**T .
!>      [ X21 ]   [    | P2 ] [ B21 ]
!>                            [  0  ]
!>
!> X11 is P-by-Q, and X21 is (M-P)-by-Q. M-P must be no larger than P,
!> Q, or M-Q. Routines SORBDB1, SORBDB2, and SORBDB4 handle cases in
!> which M-P is not the minimum dimension.
!>
!> The orthogonal matrices P1, P2, and Q1 are P-by-P, (M-P)-by-(M-P),
!> and (M-Q)-by-(M-Q), respectively. They are represented implicitly by
!> Householder vectors.
!>
!> B11 and B12 are (M-P)-by-(M-P) bidiagonal matrices represented
!> implicitly by angles THETA, PHI.
!>
!>
Parameters
[in]M
!>          M is INTEGER
!>           The number of rows X11 plus the number of rows in X21.
!> 
[in]P
!>          P is INTEGER
!>           The number of rows in X11. 0 <= P <= M. M-P <= min(P,Q,M-Q).
!> 
[in]Q
!>          Q is INTEGER
!>           The number of columns in X11 and X21. 0 <= Q <= M.
!> 
[in,out]X11
!>          X11 is REAL array, dimension (LDX11,Q)
!>           On entry, the top block of the matrix X to be reduced. On
!>           exit, the columns of tril(X11) specify reflectors for P1 and
!>           the rows of triu(X11,1) specify reflectors for Q1.
!> 
[in]LDX11
!>          LDX11 is INTEGER
!>           The leading dimension of X11. LDX11 >= P.
!> 
[in,out]X21
!>          X21 is REAL array, dimension (LDX21,Q)
!>           On entry, the bottom block of the matrix X to be reduced. On
!>           exit, the columns of tril(X21) specify reflectors for P2.
!> 
[in]LDX21
!>          LDX21 is INTEGER
!>           The leading dimension of X21. LDX21 >= M-P.
!> 
[out]THETA
!>          THETA is REAL array, dimension (Q)
!>           The entries of the bidiagonal blocks B11, B21 are defined by
!>           THETA and PHI. See Further Details.
!> 
[out]PHI
!>          PHI is REAL array, dimension (Q-1)
!>           The entries of the bidiagonal blocks B11, B21 are defined by
!>           THETA and PHI. See Further Details.
!> 
[out]TAUP1
!>          TAUP1 is REAL array, dimension (P)
!>           The scalar factors of the elementary reflectors that define
!>           P1.
!> 
[out]TAUP2
!>          TAUP2 is REAL array, dimension (M-P)
!>           The scalar factors of the elementary reflectors that define
!>           P2.
!> 
[out]TAUQ1
!>          TAUQ1 is REAL array, dimension (Q)
!>           The scalar factors of the elementary reflectors that define
!>           Q1.
!> 
[out]WORK
!>          WORK is REAL array, dimension (LWORK)
!> 
[in]LWORK
!>          LWORK is INTEGER
!>           The dimension of the array WORK. LWORK >= M-Q.
!>
!>           If LWORK = -1, then a workspace query is assumed; the routine
!>           only calculates the optimal size of the WORK array, returns
!>           this value as the first entry of the WORK array, and no error
!>           message related to LWORK is issued by XERBLA.
!> 
[out]INFO
!>          INFO is INTEGER
!>           = 0:  successful exit.
!>           < 0:  if INFO = -i, the i-th argument had an illegal value.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>  The upper-bidiagonal blocks B11, B21 are represented implicitly by
!>  angles THETA(1), ..., THETA(Q) and PHI(1), ..., PHI(Q-1). Every entry
!>  in each bidiagonal band is a product of a sine or cosine of a THETA
!>  with a sine or cosine of a PHI. See [1] or SORCSD for details.
!>
!>  P1, P2, and Q1 are represented as products of elementary reflectors.
!>  See SORCSD2BY1 for details on generating P1, P2, and Q1 using SORGQR
!>  and SORGLQ.
!> 
References:
[1] Brian D. Sutton. Computing the complete CS decomposition. Numer. Algorithms, 50(1):33-65, 2009.

Definition at line 198 of file sorbdb3.f.

201*
202* -- LAPACK computational routine --
203* -- LAPACK is a software package provided by Univ. of Tennessee, --
204* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
205*
206* .. Scalar Arguments ..
207 INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21
208* ..
209* .. Array Arguments ..
210 REAL PHI(*), THETA(*)
211 REAL TAUP1(*), TAUP2(*), TAUQ1(*), WORK(*),
212 $ X11(LDX11,*), X21(LDX21,*)
213* ..
214*
215* ====================================================================
216*
217* .. Local Scalars ..
218 REAL C, S
219 INTEGER CHILDINFO, I, ILARF, IORBDB5, LLARF, LORBDB5,
220 $ LWORKMIN, LWORKOPT
221 LOGICAL LQUERY
222* ..
223* .. External Subroutines ..
224 EXTERNAL slarf1f, slarfgp, sorbdb5, srot,
225 $ xerbla
226* ..
227* .. External Functions ..
228 REAL SNRM2
229 EXTERNAL snrm2
230* ..
231* .. Intrinsic Function ..
232 INTRINSIC atan2, cos, max, sin, sqrt
233* ..
234* .. Executable Statements ..
235*
236* Test input arguments
237*
238 info = 0
239 lquery = lwork .EQ. -1
240*
241 IF( m .LT. 0 ) THEN
242 info = -1
243 ELSE IF( 2*p .LT. m .OR. p .GT. m ) THEN
244 info = -2
245 ELSE IF( q .LT. m-p .OR. m-q .LT. m-p ) THEN
246 info = -3
247 ELSE IF( ldx11 .LT. max( 1, p ) ) THEN
248 info = -5
249 ELSE IF( ldx21 .LT. max( 1, m-p ) ) THEN
250 info = -7
251 END IF
252*
253* Compute workspace
254*
255 IF( info .EQ. 0 ) THEN
256 ilarf = 2
257 llarf = max( p, m-p-1, q-1 )
258 iorbdb5 = 2
259 lorbdb5 = q-1
260 lworkopt = max( ilarf+llarf-1, iorbdb5+lorbdb5-1 )
261 lworkmin = lworkopt
262 work(1) = real( lworkopt )
263 IF( lwork .LT. lworkmin .AND. .NOT.lquery ) THEN
264 info = -14
265 END IF
266 END IF
267 IF( info .NE. 0 ) THEN
268 CALL xerbla( 'SORBDB3', -info )
269 RETURN
270 ELSE IF( lquery ) THEN
271 RETURN
272 END IF
273*
274* Reduce rows 1, ..., M-P of X11 and X21
275*
276 DO i = 1, m-p
277*
278 IF( i .GT. 1 ) THEN
279 CALL srot( q-i+1, x11(i-1,i), ldx11, x21(i,i), ldx11, c,
280 $ s )
281 END IF
282*
283 CALL slarfgp( q-i+1, x21(i,i), x21(i,i+1), ldx21, tauq1(i) )
284 s = x21(i,i)
285 CALL slarf1f( 'R', p-i+1, q-i+1, x21(i,i), ldx21, tauq1(i),
286 $ x11(i,i), ldx11, work(ilarf) )
287 CALL slarf1f( 'R', m-p-i, q-i+1, x21(i,i), ldx21, tauq1(i),
288 $ x21(i+1,i), ldx21, work(ilarf) )
289 c = sqrt( snrm2( p-i+1, x11(i,i), 1 )**2
290 $ + snrm2( m-p-i, x21(i+1,i), 1 )**2 )
291 theta(i) = atan2( s, c )
292*
293 CALL sorbdb5( p-i+1, m-p-i, q-i, x11(i,i), 1, x21(i+1,i), 1,
294 $ x11(i,i+1), ldx11, x21(i+1,i+1), ldx21,
295 $ work(iorbdb5), lorbdb5, childinfo )
296 CALL slarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
297 IF( i .LT. m-p ) THEN
298 CALL slarfgp( m-p-i, x21(i+1,i), x21(i+2,i), 1,
299 $ taup2(i) )
300 phi(i) = atan2( x21(i+1,i), x11(i,i) )
301 c = cos( phi(i) )
302 s = sin( phi(i) )
303 CALL slarf1f( 'L', m-p-i, q-i, x21(i+1,i), 1, taup2(i),
304 $ x21(i+1,i+1), ldx21, work(ilarf) )
305 END IF
306 CALL slarf1f( 'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,
307 $ i+1), ldx11, work(ilarf) )
308*
309 END DO
310*
311* Reduce the bottom-right portion of X11 to the identity matrix
312*
313 DO i = m-p + 1, q
314 CALL slarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
315 CALL slarf1f( 'L', p-i+1, q-i, x11(i,i), 1, taup1(i), x11(i,
316 $ i+1), ldx11, work(ilarf) )
317 END DO
318*
319 RETURN
320*
321* End of SORBDB3
322*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine slarfgp(n, alpha, x, incx, tau)
SLARFGP generates an elementary reflector (Householder matrix) with non-negative beta.
Definition slarfgp.f:102
real(wp) function snrm2(n, x, incx)
SNRM2
Definition snrm2.f90:89
subroutine srot(n, sx, incx, sy, incy, c, s)
SROT
Definition srot.f:92
subroutine sorbdb5(m1, m2, n, x1, incx1, x2, incx2, q1, ldq1, q2, ldq2, work, lwork, info)
SORBDB5
Definition sorbdb5.f:155
subroutine slarf1f(side, m, n, v, incv, tau, c, ldc, work)
SLARF1F applies an elementary reflector to a general rectangular
Definition slarf1f.f:123
Here is the call graph for this function:
Here is the caller graph for this function: