~ubuntu-branches/debian/sid/octave3.0/sid

« back to all changes in this revision

Viewing changes to libcruft/lapack/zgebd2.f

  • Committer: Bazaar Package Importer
  • Author(s): Rafael Laboissiere
  • Date: 2007-12-23 16:04:15 UTC
  • Revision ID: james.westby@ubuntu.com-20071223160415-n4gk468dihy22e9v
Tags: upstream-3.0.0
ImportĀ upstreamĀ versionĀ 3.0.0

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
      SUBROUTINE ZGEBD2( M, N, A, LDA, D, E, TAUQ, TAUP, WORK, INFO )
 
2
*
 
3
*  -- LAPACK routine (version 3.1) --
 
4
*     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
 
5
*     November 2006
 
6
*
 
7
*     .. Scalar Arguments ..
 
8
      INTEGER            INFO, LDA, M, N
 
9
*     ..
 
10
*     .. Array Arguments ..
 
11
      DOUBLE PRECISION   D( * ), E( * )
 
12
      COMPLEX*16         A( LDA, * ), TAUP( * ), TAUQ( * ), WORK( * )
 
13
*     ..
 
14
*
 
15
*  Purpose
 
16
*  =======
 
17
*
 
18
*  ZGEBD2 reduces a complex general m by n matrix A to upper or lower
 
19
*  real bidiagonal form B by a unitary transformation: Q' * A * P = B.
 
20
*
 
21
*  If m >= n, B is upper bidiagonal; if m < n, B is lower bidiagonal.
 
22
*
 
23
*  Arguments
 
24
*  =========
 
25
*
 
26
*  M       (input) INTEGER
 
27
*          The number of rows in the matrix A.  M >= 0.
 
28
*
 
29
*  N       (input) INTEGER
 
30
*          The number of columns in the matrix A.  N >= 0.
 
31
*
 
32
*  A       (input/output) COMPLEX*16 array, dimension (LDA,N)
 
33
*          On entry, the m by n general matrix to be reduced.
 
34
*          On exit,
 
35
*          if m >= n, the diagonal and the first superdiagonal are
 
36
*            overwritten with the upper bidiagonal matrix B; the
 
37
*            elements below the diagonal, with the array TAUQ, represent
 
38
*            the unitary matrix Q as a product of elementary
 
39
*            reflectors, and the elements above the first superdiagonal,
 
40
*            with the array TAUP, represent the unitary matrix P as
 
41
*            a product of elementary reflectors;
 
42
*          if m < n, the diagonal and the first subdiagonal are
 
43
*            overwritten with the lower bidiagonal matrix B; the
 
44
*            elements below the first subdiagonal, with the array TAUQ,
 
45
*            represent the unitary matrix Q as a product of
 
46
*            elementary reflectors, and the elements above the diagonal,
 
47
*            with the array TAUP, represent the unitary matrix P as
 
48
*            a product of elementary reflectors.
 
49
*          See Further Details.
 
50
*
 
51
*  LDA     (input) INTEGER
 
52
*          The leading dimension of the array A.  LDA >= max(1,M).
 
53
*
 
54
*  D       (output) DOUBLE PRECISION array, dimension (min(M,N))
 
55
*          The diagonal elements of the bidiagonal matrix B:
 
56
*          D(i) = A(i,i).
 
57
*
 
58
*  E       (output) DOUBLE PRECISION array, dimension (min(M,N)-1)
 
59
*          The off-diagonal elements of the bidiagonal matrix B:
 
60
*          if m >= n, E(i) = A(i,i+1) for i = 1,2,...,n-1;
 
61
*          if m < n, E(i) = A(i+1,i) for i = 1,2,...,m-1.
 
62
*
 
63
*  TAUQ    (output) COMPLEX*16 array dimension (min(M,N))
 
64
*          The scalar factors of the elementary reflectors which
 
65
*          represent the unitary matrix Q. See Further Details.
 
66
*
 
67
*  TAUP    (output) COMPLEX*16 array, dimension (min(M,N))
 
68
*          The scalar factors of the elementary reflectors which
 
69
*          represent the unitary matrix P. See Further Details.
 
70
*
 
71
*  WORK    (workspace) COMPLEX*16 array, dimension (max(M,N))
 
72
*
 
73
*  INFO    (output) INTEGER
 
74
*          = 0: successful exit
 
75
*          < 0: if INFO = -i, the i-th argument had an illegal value.
 
76
*
 
77
*  Further Details
 
78
*  ===============
 
79
*
 
80
*  The matrices Q and P are represented as products of elementary
 
81
*  reflectors:
 
82
*
 
83
*  If m >= n,
 
84
*
 
85
*     Q = H(1) H(2) . . . H(n)  and  P = G(1) G(2) . . . G(n-1)
 
86
*
 
87
*  Each H(i) and G(i) has the form:
 
88
*
 
89
*     H(i) = I - tauq * v * v'  and G(i) = I - taup * u * u'
 
90
*
 
91
*  where tauq and taup are complex scalars, and v and u are complex
 
92
*  vectors; v(1:i-1) = 0, v(i) = 1, and v(i+1:m) is stored on exit in
 
93
*  A(i+1:m,i); u(1:i) = 0, u(i+1) = 1, and u(i+2:n) is stored on exit in
 
94
*  A(i,i+2:n); tauq is stored in TAUQ(i) and taup in TAUP(i).
 
95
*
 
96
*  If m < n,
 
97
*
 
98
*     Q = H(1) H(2) . . . H(m-1)  and  P = G(1) G(2) . . . G(m)
 
99
*
 
100
*  Each H(i) and G(i) has the form:
 
101
*
 
102
*     H(i) = I - tauq * v * v'  and G(i) = I - taup * u * u'
 
103
*
 
104
*  where tauq and taup are complex scalars, v and u are complex vectors;
 
105
*  v(1:i) = 0, v(i+1) = 1, and v(i+2:m) is stored on exit in A(i+2:m,i);
 
106
*  u(1:i-1) = 0, u(i) = 1, and u(i+1:n) is stored on exit in A(i,i+1:n);
 
107
*  tauq is stored in TAUQ(i) and taup in TAUP(i).
 
108
*
 
109
*  The contents of A on exit are illustrated by the following examples:
 
110
*
 
111
*  m = 6 and n = 5 (m > n):          m = 5 and n = 6 (m < n):
 
112
*
 
113
*    (  d   e   u1  u1  u1 )           (  d   u1  u1  u1  u1  u1 )
 
114
*    (  v1  d   e   u2  u2 )           (  e   d   u2  u2  u2  u2 )
 
115
*    (  v1  v2  d   e   u3 )           (  v1  e   d   u3  u3  u3 )
 
116
*    (  v1  v2  v3  d   e  )           (  v1  v2  e   d   u4  u4 )
 
117
*    (  v1  v2  v3  v4  d  )           (  v1  v2  v3  e   d   u5 )
 
118
*    (  v1  v2  v3  v4  v5 )
 
119
*
 
120
*  where d and e denote diagonal and off-diagonal elements of B, vi
 
121
*  denotes an element of the vector defining H(i), and ui an element of
 
122
*  the vector defining G(i).
 
123
*
 
124
*  =====================================================================
 
125
*
 
126
*     .. Parameters ..
 
127
      COMPLEX*16         ZERO, ONE
 
128
      PARAMETER          ( ZERO = ( 0.0D+0, 0.0D+0 ),
 
129
     $                   ONE = ( 1.0D+0, 0.0D+0 ) )
 
130
*     ..
 
131
*     .. Local Scalars ..
 
132
      INTEGER            I
 
133
      COMPLEX*16         ALPHA
 
134
*     ..
 
135
*     .. External Subroutines ..
 
136
      EXTERNAL           XERBLA, ZLACGV, ZLARF, ZLARFG
 
137
*     ..
 
138
*     .. Intrinsic Functions ..
 
139
      INTRINSIC          DCONJG, MAX, MIN
 
140
*     ..
 
141
*     .. Executable Statements ..
 
142
*
 
143
*     Test the input parameters
 
144
*
 
145
      INFO = 0
 
146
      IF( M.LT.0 ) THEN
 
147
         INFO = -1
 
148
      ELSE IF( N.LT.0 ) THEN
 
149
         INFO = -2
 
150
      ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
 
151
         INFO = -4
 
152
      END IF
 
153
      IF( INFO.LT.0 ) THEN
 
154
         CALL XERBLA( 'ZGEBD2', -INFO )
 
155
         RETURN
 
156
      END IF
 
157
*
 
158
      IF( M.GE.N ) THEN
 
159
*
 
160
*        Reduce to upper bidiagonal form
 
161
*
 
162
         DO 10 I = 1, N
 
163
*
 
164
*           Generate elementary reflector H(i) to annihilate A(i+1:m,i)
 
165
*
 
166
            ALPHA = A( I, I )
 
167
            CALL ZLARFG( M-I+1, ALPHA, A( MIN( I+1, M ), I ), 1,
 
168
     $                   TAUQ( I ) )
 
169
            D( I ) = ALPHA
 
170
            A( I, I ) = ONE
 
171
*
 
172
*           Apply H(i)' to A(i:m,i+1:n) from the left
 
173
*
 
174
            IF( I.LT.N )
 
175
     $         CALL ZLARF( 'Left', M-I+1, N-I, A( I, I ), 1,
 
176
     $                     DCONJG( TAUQ( I ) ), A( I, I+1 ), LDA, WORK )
 
177
            A( I, I ) = D( I )
 
178
*
 
179
            IF( I.LT.N ) THEN
 
180
*
 
181
*              Generate elementary reflector G(i) to annihilate
 
182
*              A(i,i+2:n)
 
183
*
 
184
               CALL ZLACGV( N-I, A( I, I+1 ), LDA )
 
185
               ALPHA = A( I, I+1 )
 
186
               CALL ZLARFG( N-I, ALPHA, A( I, MIN( I+2, N ) ), LDA,
 
187
     $                      TAUP( I ) )
 
188
               E( I ) = ALPHA
 
189
               A( I, I+1 ) = ONE
 
190
*
 
191
*              Apply G(i) to A(i+1:m,i+1:n) from the right
 
192
*
 
193
               CALL ZLARF( 'Right', M-I, N-I, A( I, I+1 ), LDA,
 
194
     $                     TAUP( I ), A( I+1, I+1 ), LDA, WORK )
 
195
               CALL ZLACGV( N-I, A( I, I+1 ), LDA )
 
196
               A( I, I+1 ) = E( I )
 
197
            ELSE
 
198
               TAUP( I ) = ZERO
 
199
            END IF
 
200
   10    CONTINUE
 
201
      ELSE
 
202
*
 
203
*        Reduce to lower bidiagonal form
 
204
*
 
205
         DO 20 I = 1, M
 
206
*
 
207
*           Generate elementary reflector G(i) to annihilate A(i,i+1:n)
 
208
*
 
209
            CALL ZLACGV( N-I+1, A( I, I ), LDA )
 
210
            ALPHA = A( I, I )
 
211
            CALL ZLARFG( N-I+1, ALPHA, A( I, MIN( I+1, N ) ), LDA,
 
212
     $                   TAUP( I ) )
 
213
            D( I ) = ALPHA
 
214
            A( I, I ) = ONE
 
215
*
 
216
*           Apply G(i) to A(i+1:m,i:n) from the right
 
217
*
 
218
            IF( I.LT.M )
 
219
     $         CALL ZLARF( 'Right', M-I, N-I+1, A( I, I ), LDA,
 
220
     $                     TAUP( I ), A( I+1, I ), LDA, WORK )
 
221
            CALL ZLACGV( N-I+1, A( I, I ), LDA )
 
222
            A( I, I ) = D( I )
 
223
*
 
224
            IF( I.LT.M ) THEN
 
225
*
 
226
*              Generate elementary reflector H(i) to annihilate
 
227
*              A(i+2:m,i)
 
228
*
 
229
               ALPHA = A( I+1, I )
 
230
               CALL ZLARFG( M-I, ALPHA, A( MIN( I+2, M ), I ), 1,
 
231
     $                      TAUQ( I ) )
 
232
               E( I ) = ALPHA
 
233
               A( I+1, I ) = ONE
 
234
*
 
235
*              Apply H(i)' to A(i+1:m,i+1:n) from the left
 
236
*
 
237
               CALL ZLARF( 'Left', M-I, N-I, A( I+1, I ), 1,
 
238
     $                     DCONJG( TAUQ( I ) ), A( I+1, I+1 ), LDA,
 
239
     $                     WORK )
 
240
               A( I+1, I ) = E( I )
 
241
            ELSE
 
242
               TAUQ( I ) = ZERO
 
243
            END IF
 
244
   20    CONTINUE
 
245
      END IF
 
246
      RETURN
 
247
*
 
248
*     End of ZGEBD2
 
249
*
 
250
      END