LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ zunbdb3()

subroutine zunbdb3 ( integer m,
integer p,
integer q,
complex*16, dimension(ldx11,*) x11,
integer ldx11,
complex*16, dimension(ldx21,*) x21,
integer ldx21,
double precision, dimension(*) theta,
double precision, dimension(*) phi,
complex*16, dimension(*) taup1,
complex*16, dimension(*) taup2,
complex*16, dimension(*) tauq1,
complex*16, dimension(*) work,
integer lwork,
integer info )

ZUNBDB3

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

Purpose:
!> !> ZUNBDB3 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 ZUNBDB1, ZUNBDB2, and ZUNBDB4 handle cases in !> which M-P is not the minimum dimension. !> !> The unitary 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 COMPLEX*16 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 COMPLEX*16 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 DOUBLE PRECISION array, dimension (Q) !> The entries of the bidiagonal blocks B11, B21 are defined by !> THETA and PHI. See Further Details. !>
[out]PHI
!> PHI is DOUBLE PRECISION 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 COMPLEX*16 array, dimension (P) !> The scalar factors of the elementary reflectors that define !> P1. !>
[out]TAUP2
!> TAUP2 is COMPLEX*16 array, dimension (M-P) !> The scalar factors of the elementary reflectors that define !> P2. !>
[out]TAUQ1
!> TAUQ1 is COMPLEX*16 array, dimension (Q) !> The scalar factors of the elementary reflectors that define !> Q1. !>
[out]WORK
!> WORK is COMPLEX*16 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 ZUNCSD for details. !> !> P1, P2, and Q1 are represented as products of elementary reflectors. !> See ZUNCSD2BY1 for details on generating P1, P2, and Q1 using ZUNGQR !> and ZUNGLQ. !>
References:
[1] Brian D. Sutton. Computing the complete CS decomposition. Numer. Algorithms, 50(1):33-65, 2009.

Definition at line 197 of file zunbdb3.f.

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