Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

zunbdb1 (3p)

Name

zunbdb1 - simultaneously bidiagonalize the blocks of a tall and skinny matrix with orthonomal columns

Synopsis

SUBROUTINE ZUNBDB1(M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,  TAUP1,
TAUP2, TAUQ1, WORK, LWORK, INFO)


INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21

DOUBLE PRECISION PHI(*), THETA(*)

DOUBLE  COMPLEX  TAUP1(*),  TAUP2(*),  TAUQ1(*), WORK(*), X11(LDX11,*),
X21(LDX21,*)


SUBROUTINE ZUNBDB1_64(M, P, Q, X11,  LDX11,  X21,  LDX21,  THETA,  PHI,
TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO)


INTEGER*8 INFO, LWORK, M, P, Q, LDX11, LDX21

DOUBLE PRECISION PHI(*), THETA(*)

DOUBLE  COMPLEX  TAUP1(*),  TAUP2(*),  TAUQ1(*), WORK(*), X11(LDX11,*),
X21(LDX21,*)


F95 INTERFACE
SUBROUTINE UNBDB1(M, P, Q, X11, LDX11, X21, LDX21, THETA,  PHI,  TAUP1,
TAUP2, TAUQ1, WORK, LWORK, INFO)


INTEGER :: M, P, Q, LDX11, LDX21

COMPLEX(8), DIMENSION(:) :: TAUP1, TAUP2, TAUQ1, WORK

REAL(8), DIMENSION(:) :: THETA, PHI

COMPLEX(8), DIMENSION(:,:) :: X11, X21

INTEGER(8) :: LWORK, INFO


SUBROUTINE  UNBDB1_64(M,  P,  Q,  X11,  LDX11,  X21, LDX21, THETA, PHI,
TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO)


INTEGER(8) :: M, P, Q, LDX11, LDX21

COMPLEX(8), DIMENSION(:) :: TAUP1, TAUP2, TAUQ1, WORK

REAL(8), DIMENSION(:) :: THETA, PHI

COMPLEX(8), DIMENSION(:,:) :: X11, X21

INTEGER(8)(8) :: LWORK, INFO


C INTERFACE
#include <sunperf.h>

void zunbdb1 (int m, int p, int q, doublecomplex *x11, int ldx11,  dou-
blecomplex  *x21, int ldx21, double *theta, double *phi, dou-
blecomplex  *taup1,   doublecomplex   *taup2,   doublecomplex
*tauq1, long long *info);


void  zunbdb1_64  (long  m,  long  p,  long q, doublecomplex *x11, long
ldx11, doublecomplex *x21, long ldx21, double *theta,  double
*phi,  doublecomplex *taup1, doublecomplex *taup2, doublecom-
plex *tauq1, long long *info);

Description

Oracle Solaris Studio Performance Library                          zunbdb1(3P)



NAME
       zunbdb1  - simultaneously bidiagonalize the blocks of a tall and skinny
       matrix with orthonomal columns


SYNOPSIS
       SUBROUTINE ZUNBDB1(M, P, Q, X11, LDX11, X21, LDX21, THETA, PHI,  TAUP1,
                 TAUP2, TAUQ1, WORK, LWORK, INFO)


       INTEGER INFO, LWORK, M, P, Q, LDX11, LDX21

       DOUBLE PRECISION PHI(*), THETA(*)

       DOUBLE  COMPLEX  TAUP1(*),  TAUP2(*),  TAUQ1(*), WORK(*), X11(LDX11,*),
                 X21(LDX21,*)


       SUBROUTINE ZUNBDB1_64(M, P, Q, X11,  LDX11,  X21,  LDX21,  THETA,  PHI,
                 TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO)


       INTEGER*8 INFO, LWORK, M, P, Q, LDX11, LDX21

       DOUBLE PRECISION PHI(*), THETA(*)

       DOUBLE  COMPLEX  TAUP1(*),  TAUP2(*),  TAUQ1(*), WORK(*), X11(LDX11,*),
                 X21(LDX21,*)


   F95 INTERFACE
       SUBROUTINE UNBDB1(M, P, Q, X11, LDX11, X21, LDX21, THETA,  PHI,  TAUP1,
                 TAUP2, TAUQ1, WORK, LWORK, INFO)


       INTEGER :: M, P, Q, LDX11, LDX21

       COMPLEX(8), DIMENSION(:) :: TAUP1, TAUP2, TAUQ1, WORK

       REAL(8), DIMENSION(:) :: THETA, PHI

       COMPLEX(8), DIMENSION(:,:) :: X11, X21

       INTEGER(8) :: LWORK, INFO


       SUBROUTINE  UNBDB1_64(M,  P,  Q,  X11,  LDX11,  X21, LDX21, THETA, PHI,
                 TAUP1, TAUP2, TAUQ1, WORK, LWORK, INFO)


       INTEGER(8) :: M, P, Q, LDX11, LDX21

       COMPLEX(8), DIMENSION(:) :: TAUP1, TAUP2, TAUQ1, WORK

       REAL(8), DIMENSION(:) :: THETA, PHI

       COMPLEX(8), DIMENSION(:,:) :: X11, X21

       INTEGER(8)(8) :: LWORK, INFO


   C INTERFACE
       #include <sunperf.h>

       void zunbdb1 (int m, int p, int q, doublecomplex *x11, int ldx11,  dou-
                 blecomplex  *x21, int ldx21, double *theta, double *phi, dou-
                 blecomplex  *taup1,   doublecomplex   *taup2,   doublecomplex
                 *tauq1, long long *info);


       void  zunbdb1_64  (long  m,  long  p,  long q, doublecomplex *x11, long
                 ldx11, doublecomplex *x21, long ldx21, double *theta,  double
                 *phi,  doublecomplex *taup1, doublecomplex *taup2, doublecom-
                 plex *tauq1, long long *info);


PURPOSE
       zunbdb1 simultaneously bidiagonalizes the blocks of a tall  and  skinny
       matrix X with orthonomal columns:

                             [ B11 ]
       [ X11 ]   [ P1 |    ] [  0  ]
       [-----] = [---------] [-----] Q1**T .
       [ X21 ]   [    | P2 ] [ B21 ]
       [  0  ]


   X11 is P-by-Q, and X21 is (M-P)-by-Q. Q must be no larger than P,
       M-P,  or  M-Q.  Routines  ZUNBDB2, ZUNBDB3, and ZUNBDB4 handle cases in
       which Q 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 House-
       holder vectors.

       B11 and B12 are Q-by-Q bidiagonal matrices  represented  implicitly  by
       angles THETA, PHI.



ARGUMENTS
       M (input)
                 M is INTEGER
                 The number of rows X11 plus the number of rows in X21.


       P (input)
                 P is INTEGER
                 The number of rows in X11. 0 <= P <= M.


       Q (input)
                 Q is INTEGER
                 The  number of columns in X11 and X21. 0 <= Q <= MIN(P,M-P,M-
                 Q).


       X11 (input/output)
                 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.


       LDX11 (input)
                 LDX11 is INTEGER
                 The leading dimension of X11. LDX11 >= P.


       X21 (input/output)
                 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.


       LDX21 (input)
                 LDX21 is INTEGER
                 The leading dimension of X21. LDX21 >= M-P.


       THETA (output)
                 THETA is DOUBLE PRECISION array, dimension (Q)
                 The entries of the bidiagonal blocks B11, B21 are defined  by
                 THETA and PHI. See Further Details.


       PHI (output)
                 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.


       TAUP1 (output)
                 TAUP1 is COMPLEX*16 array, dimension (P)
                 The scalar factors of the elementary reflectors  that  define
                 P1.


       TAUP2 (output)
                 TAUP2 is COMPLEX*16 array, dimension (M-P)
                 The  scalar  factors of the elementary reflectors that define
                 P2.


       TAUQ1 (output)
                 TAUQ1 is COMPLEX*16 array, dimension (Q)
                 The scalar factors of the elementary reflectors  that  define
                 Q1.


       WORK (output)
                 WORK is COMPLEX*16 array, dimension (LWORK)


       LWORK (input)
                 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.


       INFO (output)
                 INFO is INTEGER
                 = 0:  successful exit;
                 < 0:  if INFO = -i, the i-th argument had an illegal value.


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.



                                  7 Nov 2015                       zunbdb1(3P)