Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

cgebrd (3p)

Name

cgebrd - N matrix A to upper or lower bidiagonal form B by a unitary transformation

Synopsis

SUBROUTINE CGEBRD(M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK, INFO)

COMPLEX A(LDA,*), TAUQ(*), TAUP(*), WORK(*)
INTEGER M, N, LDA, LWORK, INFO
REAL D(*), E(*)

SUBROUTINE CGEBRD_64(M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK,
INFO)

COMPLEX A(LDA,*), TAUQ(*), TAUP(*), WORK(*)
INTEGER*8 M, N, LDA, LWORK, INFO
REAL D(*), E(*)




F95 INTERFACE
SUBROUTINE GEBRD(M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK,
INFO)

COMPLEX, DIMENSION(:) :: TAUQ, TAUP, WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER :: M, N, LDA, LWORK, INFO
REAL, DIMENSION(:) :: D, E

SUBROUTINE GEBRD_64(M, N, A, LDA, D, E, TAUQ, TAUP, WORK,
LWORK, INFO)

COMPLEX, DIMENSION(:) :: TAUQ, TAUP, WORK
COMPLEX, DIMENSION(:,:) :: A
INTEGER(8) :: M, N, LDA, LWORK, INFO
REAL, DIMENSION(:) :: D, E




C INTERFACE
#include <sunperf.h>

void cgebrd(int m, int n, complex *a, int lda, float *d, float *e, com-
plex *tauq, complex *taup, int *info);

void  cgebrd_64(long  m,  long n, complex *a, long lda, float *d, float
*e, complex *tauq, complex *taup, long *info);

Description

Oracle Solaris Studio Performance Library                           cgebrd(3P)



NAME
       cgebrd  -  reduce  a  general complex M-by-N matrix A to upper or lower
       bidiagonal form B by a unitary transformation


SYNOPSIS
       SUBROUTINE CGEBRD(M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK, INFO)

       COMPLEX A(LDA,*), TAUQ(*), TAUP(*), WORK(*)
       INTEGER M, N, LDA, LWORK, INFO
       REAL D(*), E(*)

       SUBROUTINE CGEBRD_64(M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK,
             INFO)

       COMPLEX A(LDA,*), TAUQ(*), TAUP(*), WORK(*)
       INTEGER*8 M, N, LDA, LWORK, INFO
       REAL D(*), E(*)




   F95 INTERFACE
       SUBROUTINE GEBRD(M, N, A, LDA, D, E, TAUQ, TAUP, WORK, LWORK,
              INFO)

       COMPLEX, DIMENSION(:) :: TAUQ, TAUP, WORK
       COMPLEX, DIMENSION(:,:) :: A
       INTEGER :: M, N, LDA, LWORK, INFO
       REAL, DIMENSION(:) :: D, E

       SUBROUTINE GEBRD_64(M, N, A, LDA, D, E, TAUQ, TAUP, WORK,
              LWORK, INFO)

       COMPLEX, DIMENSION(:) :: TAUQ, TAUP, WORK
       COMPLEX, DIMENSION(:,:) :: A
       INTEGER(8) :: M, N, LDA, LWORK, INFO
       REAL, DIMENSION(:) :: D, E




   C INTERFACE
       #include <sunperf.h>

       void cgebrd(int m, int n, complex *a, int lda, float *d, float *e, com-
                 plex *tauq, complex *taup, int *info);

       void  cgebrd_64(long  m,  long n, complex *a, long lda, float *d, float
                 *e, complex *tauq, complex *taup, long *info);



PURPOSE
       cgebrd reduces a general complex M-by-N matrix  A  to  upper  or  lower
       bidiagonal form B by a unitary transformation: Q**H * A * P = B.

       If m >= n, B is upper bidiagonal; if m < n, B is lower bidiagonal.


ARGUMENTS
       M (input) The number of rows in the matrix A.  M >= 0.


       N (input) The number of columns in the matrix A.  N >= 0.


       A (input/output)
                 On entry, the M-by-N general matrix to be reduced.
                 On exit,
                 if m >= n, the diagonal and the first superdiagonal are over-
                 written with the upper  bidiagonal  matrix  B;  the  elements
                 below  the  diagonal, with the array TAUQ, represent the uni-
                 tary matrix Q as a product of elementary reflectors, and  the
                 elements  above the first superdiagonal, with the array TAUP,
                 represent the unitary matrix P as  a  product  of  elementary
                 reflectors;
                 if  m  <  n, the diagonal and the first subdiagonal are over-
                 written with the lower  bidiagonal  matrix  B;  the  elements
                 below  the  first subdiagonal, with the array TAUQ, represent
                 the unitary matrix Q as a product of  elementary  reflectors,
                 and  the  elements  above  the diagonal, with the array TAUP,
                 represent the unitary matrix P as  a  product  of  elementary
                 reflectors.
                 See Further Details.


       LDA (input)
                 The leading dimension of the array A.
                 LDA >= max(1,M).


       D (output)
                 The  diagonal  elements  of  the  bidiagonal matrix B: D(i) =
                 A(i,i).


       E (output)
                 The off-diagonal elements of the bidiagonal matrix B:
                 if m >= n, E(i) = A(i,i+1) for i = 1,2,...,n-1;
                 if m < n, E(i) = A(i+1,i) for i = 1,2,...,m-1.


       TAUQ (output)
                 The scalar factors of the elementary reflectors which  repre-
                 sent the unitary matrix Q.
                 See Further Details.


       TAUP (output)
                 The  scalar factors of the elementary reflectors which repre-
                 sent the unitary matrix P.
                 See Further Details.


       WORK (workspace)
                 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.


       LWORK (input)
                 The length of the array  WORK.   LWORK  >=  max(1,M,N).   For
                 optimum  performance LWORK >= (M+N)*NB, where NB is the opti-
                 mal blocksize.

                 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)
                 = 0:  successful exit;
                 < 0:  if INFO = -i, the i-th argument had an illegal value.

FURTHER DETAILS
       The  matrices Q and P are represented as products of elementary reflec-
       tors:

       If m >= n,

       Q = H(1) H(2) . . . H(n)  and  P = G(1) G(2) . . . G(n-1)

       Each H(i) and G(i) has the form:

       H(i) = I - tauq * v * v'  and G(i) = I - taup * u * u'

       where tauq and taup are complex scalars, and v and u are  complex  vec-
       tors;  v(1:i-1)  =  0,  v(i)  =  1,  and  v(i+1:m) is stored on exit in
       A(i+1:m,i); u(1:i) = 0, u(i+1) = 1, and u(i+2:n) is stored on  exit  in
       A(i,i+2:n); tauq is stored in TAUQ(i) and taup in TAUP(i).

       If m < n,

       Q = H(1) H(2) . . . H(m-1)  and  P = G(1) G(2) . . . G(m)

       Each H(i) and G(i) has the form:

       H(i) = I - tauq * v * v'  and G(i) = I - taup * u * u'

       where  tauq  and taup are complex scalars, and v and u are complex vec-
       tors; v(1:i) = 0, v(i+1) =  1,  and  v(i+2:m)  is  stored  on  exit  in
       A(i+2:m,i);  u(1:i-1)  = 0, u(i) = 1, and u(i+1:n) is stored on exit in
       A(i,i+1:n); tauq is stored in TAUQ(i) and taup in TAUP(i).

       The contents of A on exit are illustrated by the following examples:

       m = 6 and n = 5 (m > n):          m = 5 and n = 6 (m < n):

       (  d   e   u1  u1  u1 )       (  d   u1  u1  u1  u1  u1 )
       (  v1  d   e   u2  u2 )       (  e   d   u2  u2  u2  u2 )
       (  v1  v2  d   e   u3 )       (  v1  e   d   u3  u3  u3 )
       (  v1  v2  v3  d   e  )       (  v1  v2  e   d   u4  u4 )
       (  v1  v2  v3  v4  d  )       (  v1  v2  v3  e   d   u5 )
       (  v1  v2  v3  v4  v5 )

       where d and e denote  diagonal  and  off-diagonal  elements  of  B,  vi
       denotes  an  element  of the vector defining H(i), and ui an element of
       the vector defining G(i).




                                  7 Nov 2015                        cgebrd(3P)