Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cunbdb4 (3p)

Name

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

Synopsis

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


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

REAL PHI(*), THETA(*)

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


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


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

REAL PHI(*), THETA(*)

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


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


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

REAL, DIMENSION(:) :: THETA, PHI

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

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


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


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

REAL, DIMENSION(:) :: THETA, PHI

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

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


C INTERFACE
#include <sunperf.h>

void cunbdb4 (int m, int p, int q, floatcomplex *x11, int ldx11, float-
complex  *x21, int ldx21, float *theta, float *phi, floatcom-
plex *taup1, floatcomplex *taup2, floatcomplex *tauq1, float-
complex *phantom, int *info);


void cunbdb4_64 (long m, long p, long q, floatcomplex *x11, long ldx11,
floatcomplex *x21, long  ldx21,  float  *theta,  float  *phi,
floatcomplex   *taup1,   floatcomplex   *taup2,  floatcomplex
*tauq1, floatcomplex *phantom, long *info);

Description

Oracle Solaris Studio Performance Library                          cunbdb4(3P)



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


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


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

       REAL PHI(*), THETA(*)

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


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


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

       REAL PHI(*), THETA(*)

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


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


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

       REAL, DIMENSION(:) :: THETA, PHI

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

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


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


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

       REAL, DIMENSION(:) :: THETA, PHI

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

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


   C INTERFACE
       #include <sunperf.h>

       void cunbdb4 (int m, int p, int q, floatcomplex *x11, int ldx11, float-
                 complex  *x21, int ldx21, float *theta, float *phi, floatcom-
                 plex *taup1, floatcomplex *taup2, floatcomplex *tauq1, float-
                 complex *phantom, int *info);


       void cunbdb4_64 (long m, long p, long q, floatcomplex *x11, long ldx11,
                 floatcomplex *x21, long  ldx21,  float  *theta,  float  *phi,
                 floatcomplex   *taup1,   floatcomplex   *taup2,  floatcomplex
                 *tauq1, floatcomplex *phantom, long *info);


PURPOSE
       cunbdb4 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. M-Q must be no larger than P,
       M-P, or Q. Routines CUNBDB1, CUNBDB2, and CUNBDB3 handle cases in which
       M-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 (M-Q)-by-(M-Q) bidiagonal matrices represented  implic-
       itly 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 <= M and M-Q <=
                 min(P,M-P,Q).


       X11 (input/output)
                 X11 is COMPLEX 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 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 REAL array, dimension (Q)
                 The entries of the bidiagonal blocks B11, B21 are defined  by
                 THETA and PHI. See Further Details.


       PHI (output)
                 PHI is REAL 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 array, dimension (P)
                 The scalar factors of the elementary reflectors  that  define
                 P1.


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


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


       PHANTOM (output)
                 PHANTOM is COMPLEX array, dimension (M)
                 The  routine  computes  an  M-by-1  column  vector  Y that is
                 orthogonal to the columns of [ X11; X21 ].  PHANTOM(1:P)  and
                 PHANTOM(P+1:M)  contain  Householder  vectors  for Y(1:P) and
                 Y(P+1:M), respectively.


       WORK (output)
                 WORK is COMPLEX 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 CUNCSD for details.

       P1, P2, and Q1 are represented as products  of  elementary  reflectors.
       See  CUNCSD2BY1  for  details on generating P1, P2, and Q1 using CUNGQR
       and CUNGLQ.



                                  7 Nov 2015                       cunbdb4(3P)