Contents


NAME

     cgbbrd - reduce a complex general m-by-n band  matrix  A  to
     real upper bidiagonal form B by a unitary transformation

SYNOPSIS

     SUBROUTINE CGBBRD(VECT, M, N, NCC, KL, KU, AB, LDAB, D, E, Q, LDQ,
           PT, LDPT, C, LDC, WORK, RWORK, INFO)

     CHARACTER * 1 VECT
     COMPLEX AB(LDAB,*), Q(LDQ,*), PT(LDPT,*), C(LDC,*), WORK(*)
     INTEGER M, N, NCC, KL, KU, LDAB, LDQ, LDPT, LDC, INFO
     REAL D(*), E(*), RWORK(*)

     SUBROUTINE CGBBRD_64(VECT, M, N, NCC, KL, KU, AB, LDAB, D, E, Q, LDQ,
           PT, LDPT, C, LDC, WORK, RWORK, INFO)

     CHARACTER * 1 VECT
     COMPLEX AB(LDAB,*), Q(LDQ,*), PT(LDPT,*), C(LDC,*), WORK(*)
     INTEGER*8 M, N, NCC, KL, KU, LDAB, LDQ, LDPT, LDC, INFO
     REAL D(*), E(*), RWORK(*)

  F95 INTERFACE
     SUBROUTINE GBBRD(VECT, M, [N], [NCC], KL, KU, AB, [LDAB], D, E, Q,
            [LDQ], PT, [LDPT], C, [LDC], [WORK], [RWORK], [INFO])

     CHARACTER(LEN=1) :: VECT
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: AB, Q, PT, C
     INTEGER :: M, N, NCC, KL, KU, LDAB, LDQ, LDPT, LDC, INFO
     REAL, DIMENSION(:) :: D, E, RWORK

     SUBROUTINE GBBRD_64(VECT, M, [N], [NCC], KL, KU, AB, [LDAB], D, E,
            Q, [LDQ], PT, [LDPT], C, [LDC], [WORK], [RWORK], [INFO])

     CHARACTER(LEN=1) :: VECT
     COMPLEX, DIMENSION(:) :: WORK
     COMPLEX, DIMENSION(:,:) :: AB, Q, PT, C
     INTEGER(8) :: M, N, NCC, KL, KU, LDAB, LDQ, LDPT, LDC, INFO
     REAL, DIMENSION(:) :: D, E, RWORK

  C INTERFACE
     #include <sunperf.h>

     void cgbbrd(char vect, int m, int n, int ncc,  int  kl,  int
               ku,  complex  *ab,  int  ldab, float *d, float *e,
               complex *q, int ldq, complex *pt, int  ldpt,  com-
               plex *c, int ldc, int *info);
     void cgbbrd_64(char vect, long m, long n, long ncc, long kl,
               long  ku,  complex *ab, long ldab, float *d, float
               *e, complex *q, long ldq, complex *pt, long  ldpt,
               complex *c, long ldc, long *info);

PURPOSE

     cgbbrd reduces a complex general m-by-n  band  matrix  A  to
     real upper bidiagonal form B by a unitary transformation: Q'
     * A * P = B.

     The routine computes B, and optionally forms  Q  or  P',  or
     computes Q'*C for a given matrix C.

ARGUMENTS

     VECT (input)
               Specifies whether or not the matrices Q and P' are
               to be formed.  = 'N': do not form Q or P';
               = 'Q': form Q only;
               = 'P': form P' only;
               = 'B': form both.

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

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

     NCC (input)
               The number of columns of the matrix C.  NCC >= 0.

     KL (input)
               The number of subdiagonals of the matrix A. KL  >=
               0.

     KU (input)
               The number of superdiagonals of the matrix  A.  KU
               >= 0.

     AB (input/output)
               On entry, the m-by-n band matrix A, stored in rows
               1  to  KL+KU+1.  The j-th column of A is stored in
               the j-th  column  of  the  array  AB  as  follows:
               AB(ku+1+i-j,j)     =     A(i,j)    for    max(1,j-
               ku)<=i<=min(m,j+kl).  On exit, A is overwritten by
               values generated during the reduction.
     LDAB (input)
               The leading dimension of  the  array  A.  LDAB  >=
               KL+KU+1.

     D (output)
               The diagonal elements of the bidiagonal matrix B.

     E (output)
               The  superdiagonal  elements  of  the   bidiagonal
               matrix B.

     Q (output)
               If VECT = 'Q' or 'B', the m-by-m unitary matrix Q.
               If  VECT  =  'N' or 'P', the array Q is not refer-
               enced.

     LDQ (input)
               The leading dimension of  the  array  Q.   LDQ  >=
               max(1,M) if VECT = 'Q' or 'B'; LDQ >= 1 otherwise.

     PT (output)
               If VECT = 'P' or 'B', the  n-by-n  unitary  matrix
               P'.   If  VECT  =  'N' or 'Q', the array PT is not
               referenced.

     LDPT (input)
               The leading dimension of the array  PT.   LDPT  >=
               max(1,N)  if  VECT  = 'P' or 'B'; LDPT >= 1 other-
               wise.

     C (input/output)
               On entry, an m-by-ncc matrix C.   On  exit,  C  is
               overwritten by Q'*C.  C is not referenced if NCC =
               0.

     LDC (input)
               The leading dimension of  the  array  C.   LDC  >=
               max(1,M) if NCC > 0; LDC >= 1 if NCC = 0.

     WORK (workspace)
               dimension(MAX(M,N))

     RWORK (workspace)
               dimension(MAX(M,N))

     INFO (output)
               = 0:  successful exit.
               < 0:  if INFO = -i, the i-th argument had an ille-
               gal value.