3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZUNBDB6 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zunbdb6.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zunbdb6.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zunbdb6.f">
21 * SUBROUTINE ZUNBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
22 * LDQ2, WORK, LWORK, INFO )
24 * .. Scalar Arguments ..
25 * INTEGER INCX1, INCX2, INFO, LDQ1, LDQ2, LWORK, M1, M2,
28 * .. Array Arguments ..
29 * COMPLEX*16 Q1(LDQ1,*), Q2(LDQ2,*), WORK(*), X1(*), X2(*)
38 *> ZUNBDB6 orthogonalizes the column vector
41 *> with respect to the columns of
44 *> The columns of Q must be orthonormal.
46 *> If the projection is zero according to Kahan's "twice is enough"
47 *> criterion, then the zero vector is returned.
57 *> The dimension of X1 and the number of rows in Q1. 0 <= M1.
63 *> The dimension of X2 and the number of rows in Q2. 0 <= M2.
69 *> The number of columns in Q1 and Q2. 0 <= N.
74 *> X1 is COMPLEX*16 array, dimension (M1)
75 *> On entry, the top part of the vector to be orthogonalized.
76 *> On exit, the top part of the projected vector.
82 *> Increment for entries of X1.
87 *> X2 is COMPLEX*16 array, dimension (M2)
88 *> On entry, the bottom part of the vector to be
89 *> orthogonalized. On exit, the bottom part of the projected
96 *> Increment for entries of X2.
101 *> Q1 is COMPLEX*16 array, dimension (LDQ1, N)
102 *> The top part of the orthonormal basis matrix.
108 *> The leading dimension of Q1. LDQ1 >= M1.
113 *> Q2 is COMPLEX*16 array, dimension (LDQ2, N)
114 *> The bottom part of the orthonormal basis matrix.
120 *> The leading dimension of Q2. LDQ2 >= M2.
125 *> WORK is COMPLEX*16 array, dimension (LWORK)
131 *> The dimension of the array WORK. LWORK >= N.
137 *> = 0: successful exit.
138 *> < 0: if INFO = -i, the i-th argument had an illegal value.
144 *> \author Univ. of Tennessee
145 *> \author Univ. of California Berkeley
146 *> \author Univ. of Colorado Denver
151 *> \ingroup complex16OTHERcomputational
153 * =====================================================================
154 SUBROUTINE ZUNBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
155 $ LDQ2, WORK, LWORK, INFO )
157 * -- LAPACK computational routine (version 3.5.0) --
158 * -- LAPACK is a software package provided by Univ. of Tennessee, --
159 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162 * .. Scalar Arguments ..
163 INTEGER INCX1, INCX2, INFO, LDQ1, LDQ2, LWORK, M1, M2,
166 * .. Array Arguments ..
167 COMPLEX*16 Q1(LDQ1,*), Q2(LDQ2,*), WORK(*), X1(*), X2(*)
170 * =====================================================================
173 DOUBLE PRECISION ALPHASQ, REALONE, REALZERO
174 PARAMETER ( ALPHASQ = 0.01D0, REALONE = 1.0D0,
176 COMPLEX*16 NEGONE, ONE, ZERO
177 PARAMETER ( NEGONE = (-1.0D0,0.0D0), ONE = (1.0D0,0.0D0),
178 $ ZERO = (0.0D0,0.0D0) )
180 * .. Local Scalars ..
182 DOUBLE PRECISION NORMSQ1, NORMSQ2, SCL1, SCL2, SSQ1, SSQ2
184 * .. External Subroutines ..
185 EXTERNAL ZGEMV, ZLASSQ, XERBLA
187 * .. Intrinsic Function ..
190 * .. Executable Statements ..
192 * Test input arguments
197 ELSE IF( M2 .LT. 0 ) THEN
199 ELSE IF( N .LT. 0 ) THEN
201 ELSE IF( INCX1 .LT. 1 ) THEN
203 ELSE IF( INCX2 .LT. 1 ) THEN
205 ELSE IF( LDQ1 .LT. MAX( 1, M1 ) ) THEN
207 ELSE IF( LDQ2 .LT. MAX( 1, M2 ) ) THEN
209 ELSE IF( LWORK .LT. N ) THEN
213 IF( INFO .NE. 0 ) THEN
214 CALL XERBLA( 'ZUNBDB6', -INFO )
218 * First, project X onto the orthogonal complement of Q's column
223 CALL ZLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
226 CALL ZLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
227 NORMSQ1 = SCL1**2*SSQ1 + SCL2**2*SSQ2
234 CALL ZGEMV( 'C', M1, N, ONE, Q1, LDQ1, X1, INCX1, ZERO, WORK,
238 CALL ZGEMV( 'C', M2, N, ONE, Q2, LDQ2, X2, INCX2, ONE, WORK, 1 )
240 CALL ZGEMV( 'N', M1, N, NEGONE, Q1, LDQ1, WORK, 1, ONE, X1,
242 CALL ZGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
247 CALL ZLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
250 CALL ZLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
251 NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
253 * If projection is sufficiently large in norm, then stop.
254 * If projection is zero, then stop.
255 * Otherwise, project again.
257 IF( NORMSQ2 .GE. ALPHASQ*NORMSQ1 ) THEN
261 IF( NORMSQ2 .EQ. ZERO ) THEN
276 CALL ZGEMV( 'C', M1, N, ONE, Q1, LDQ1, X1, INCX1, ZERO, WORK,
280 CALL ZGEMV( 'C', M2, N, ONE, Q2, LDQ2, X2, INCX2, ONE, WORK, 1 )
282 CALL ZGEMV( 'N', M1, N, NEGONE, Q1, LDQ1, WORK, 1, ONE, X1,
284 CALL ZGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
289 CALL ZLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
292 CALL ZLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
293 NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
295 * If second projection is sufficiently large in norm, then do
296 * nothing more. Alternatively, if it shrunk significantly, then
297 * truncate it to zero.
299 IF( NORMSQ2 .LT. ALPHASQ*NORMSQ1 ) THEN