1ZLABRD(1)           LAPACK auxiliary routine (version 3.1)           ZLABRD(1)
2
3
4

NAME

6       ZLABRD  -  the  first  NB  rows and columns of a complex general m by n
7       matrix A to upper or lower real bidiagonal form by a unitary  transfor‐
8       mation Q' * A * P, and returns the matrices X and Y which are needed to
9       apply the transformation to the unreduced part of A
10

SYNOPSIS

12       SUBROUTINE ZLABRD( M, N, NB, A, LDA, D, E, TAUQ, TAUP, X, LDX, Y, LDY )
13
14           INTEGER        LDA, LDX, LDY, M, N, NB
15
16           DOUBLE         PRECISION D( * ), E( * )
17
18           COMPLEX*16     A( LDA, * ), TAUP( * ), TAUQ( * ), X( LDX, *  ),  Y(
19                          LDY, * )
20

PURPOSE

22       ZLABRD  reduces the first NB rows and columns of a complex general m by
23       n matrix A to upper or lower real bidiagonal form by a  unitary  trans‐
24       formation Q' * A * P, and returns the matrices X and Y which are needed
25       to apply the transformation to the unreduced part of A.
26
27       If m >= n, A is reduced to upper bidiagonal form; if m <  n,  to  lower
28       bidiagonal form.
29
30       This is an auxiliary routine called by ZGEBRD
31
32

ARGUMENTS

34       M       (input) INTEGER
35               The number of rows in the matrix A.
36
37       N       (input) INTEGER
38               The number of columns in the matrix A.
39
40       NB      (input) INTEGER
41               The number of leading rows and columns of A to be reduced.
42
43       A       (input/output) COMPLEX*16 array, dimension (LDA,N)
44               On  entry,  the  m by n general matrix to be reduced.  On exit,
45               the first NB rows and columns of the  matrix  are  overwritten;
46               the rest of the array is unchanged.  If m >= n, elements on and
47               below the diagonal in the first  NB  columns,  with  the  array
48               TAUQ, represent the unitary matrix Q as a product of elementary
49               reflectors; and elements above the diagonal  in  the  first  NB
50               rows,  with the array TAUP, represent the unitary matrix P as a
51               product of elementary reflectors.  If m < n, elements below the
52               diagonal  in  the first NB columns, with the array TAUQ, repre‐
53               sent the unitary matrix Q as a product  of  elementary  reflec‐
54               tors,  and  elements  on and above the diagonal in the first NB
55               rows, with the array TAUP, represent the unitary matrix P as  a
56               product  of  elementary  reflectors.  See Further Details.  LDA
57               (input) INTEGER The leading dimension of the array A.   LDA  >=
58               max(1,M).
59
60       D       (output) DOUBLE PRECISION array, dimension (NB)
61               The  diagonal  elements of the first NB rows and columns of the
62               reduced matrix.  D(i) = A(i,i).
63
64       E       (output) DOUBLE PRECISION array, dimension (NB)
65               The off-diagonal elements of the first NB rows and  columns  of
66               the reduced matrix.
67
68       TAUQ    (output) COMPLEX*16 array dimension (NB)
69               The scalar factors of the elementary reflectors which represent
70               the unitary matrix Q. See Further  Details.   TAUP     (output)
71               COMPLEX*16 array, dimension (NB) The scalar factors of the ele‐
72               mentary reflectors which represent the unitary  matrix  P.  See
73               Further  Details.  X       (output) COMPLEX*16 array, dimension
74               (LDX,NB) The m-by-nb matrix X required to update the  unreduced
75               part of A.
76
77       LDX     (input) INTEGER
78               The leading dimension of the array X. LDX >= max(1,M).
79
80       Y       (output) COMPLEX*16 array, dimension (LDY,NB)
81               The  n-by-nb  matrix Y required to update the unreduced part of
82               A.
83
84       LDY     (input) INTEGER
85               The leading dimension of the array Y. LDY >= max(1,N).
86

FURTHER DETAILS

88       The matrices Q and P are represented as products of elementary  reflec‐
89       tors:
90
91          Q = H(1) H(2) . . . H(nb)  and  P = G(1) G(2) . . . G(nb)
92
93       Each H(i) and G(i) has the form:
94
95          H(i) = I - tauq * v * v'  and G(i) = I - taup * u * u'
96
97       where  tauq  and taup are complex scalars, and v and u are complex vec‐
98       tors.
99
100       If m >= n, v(1:i-1) = 0, v(i) = 1, and v(i:m)  is  stored  on  exit  in
101       A(i:m,i);  u(1:i)  =  0,  u(i+1) = 1, and u(i+1:n) is stored on exit in
102       A(i,i+1:n); tauq is stored in TAUQ(i) and taup in TAUP(i).
103
104       If m < n, v(1:i) = 0, v(i+1) = 1, and v(i+1:m) is  stored  on  exit  in
105       A(i+2:m,i);  u(1:i-1)  =  0,  u(i) = 1, and u(i:n) is stored on exit in
106       A(i,i+1:n); tauq is stored in TAUQ(i) and taup in TAUP(i).
107
108       The elements of the vectors v and u together form the m-by-nb matrix  V
109       and  the nb-by-n matrix U' which are needed, with X and Y, to apply the
110       transformation to the unreduced part  of  the  matrix,  using  a  block
111       update of the form:  A := A - V*Y' - X*U'.
112
113       The  contents  of  A  on exit are illustrated by the following examples
114       with nb = 2:
115
116       m = 6 and n = 5 (m > n):          m = 5 and n = 6 (m < n):
117
118         (  1   1   u1  u1  u1 )           (  1   u1  u1  u1  u1  u1 )
119         (  v1  1   1   u2  u2 )           (  1   1   u2  u2  u2  u2 )
120         (  v1  v2  a   a   a  )           (  v1  1   a   a   a   a  )
121         (  v1  v2  a   a   a  )           (  v1  v2  a   a   a   a  )
122         (  v1  v2  a   a   a  )           (  v1  v2  a   a   a   a  )
123         (  v1  v2  a   a   a  )
124
125       where a denotes an element of the original matrix which  is  unchanged,
126       vi denotes an element of the vector defining H(i), and ui an element of
127       the vector defining G(i).
128
129
130
131
132 LAPACK auxiliary routine (versionNo3v.e1m)ber 2006                       ZLABRD(1)
Impressum