3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DORBDB6 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dorbdb6.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dorbdb6.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorbdb6.f">
21 * SUBROUTINE DORBDB6( 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 * DOUBLE PRECISION Q1(LDQ1,*), Q2(LDQ2,*), WORK(*), X1(*), X2(*)
38 *> DORBDB6 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 DOUBLE PRECISION 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 DOUBLE PRECISION 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 DOUBLE PRECISION array, dimension (LDQ1, N)
102 *> The top part of the orthonormal basis matrix.
108 *> The leading dimension of Q1. LDQ1 >= M1.
113 *> Q2 is DOUBLE PRECISION array, dimension (LDQ2, N)
114 *> The bottom part of the orthonormal basis matrix.
120 *> The leading dimension of Q2. LDQ2 >= M2.
125 *> WORK is DOUBLE PRECISION 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 doubleOTHERcomputational
153 * =====================================================================
154 SUBROUTINE DORBDB6( 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 DOUBLE PRECISION Q1(LDQ1,*), Q2(LDQ2,*), WORK(*), X1(*), X2(*)
170 * =====================================================================
173 DOUBLE PRECISION ALPHASQ, REALONE, REALZERO
174 PARAMETER ( ALPHASQ = 0.01D0, REALONE = 1.0D0,
176 DOUBLE PRECISION NEGONE, ONE, ZERO
177 PARAMETER ( NEGONE = -1.0D0, ONE = 1.0D0, ZERO = 0.0D0 )
179 * .. Local Scalars ..
181 DOUBLE PRECISION NORMSQ1, NORMSQ2, SCL1, SCL2, SSQ1, SSQ2
183 * .. External Subroutines ..
184 EXTERNAL DGEMV, DLASSQ, XERBLA
186 * .. Intrinsic Function ..
189 * .. Executable Statements ..
191 * Test input arguments
196 ELSE IF( M2 .LT. 0 ) THEN
198 ELSE IF( N .LT. 0 ) THEN
200 ELSE IF( INCX1 .LT. 1 ) THEN
202 ELSE IF( INCX2 .LT. 1 ) THEN
204 ELSE IF( LDQ1 .LT. MAX( 1, M1 ) ) THEN
206 ELSE IF( LDQ2 .LT. MAX( 1, M2 ) ) THEN
208 ELSE IF( LWORK .LT. N ) THEN
212 IF( INFO .NE. 0 ) THEN
213 CALL XERBLA( 'DORBDB6', -INFO )
217 * First, project X onto the orthogonal complement of Q's column
222 CALL DLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
225 CALL DLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
226 NORMSQ1 = SCL1**2*SSQ1 + SCL2**2*SSQ2
233 CALL DGEMV( 'C', M1, N, ONE, Q1, LDQ1, X1, INCX1, ZERO, WORK,
237 CALL DGEMV( 'C', M2, N, ONE, Q2, LDQ2, X2, INCX2, ONE, WORK, 1 )
239 CALL DGEMV( 'N', M1, N, NEGONE, Q1, LDQ1, WORK, 1, ONE, X1,
241 CALL DGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
246 CALL DLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
249 CALL DLASSQ( M2, X2, INCX2, SCL2, SSQ2 )
250 NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
252 * If projection is sufficiently large in norm, then stop.
253 * If projection is zero, then stop.
254 * Otherwise, project again.
256 IF( NORMSQ2 .GE. ALPHASQ*NORMSQ1 ) THEN
260 IF( NORMSQ2 .EQ. ZERO ) THEN
275 CALL DGEMV( 'C', M1, N, ONE, Q1, LDQ1, X1, INCX1, ZERO, WORK,
279 CALL DGEMV( 'C', M2, N, ONE, Q2, LDQ2, X2, INCX2, ONE, WORK, 1 )
281 CALL DGEMV( 'N', M1, N, NEGONE, Q1, LDQ1, WORK, 1, ONE, X1,
283 CALL DGEMV( 'N', M2, N, NEGONE, Q2, LDQ2, WORK, 1, ONE, X2,
288 CALL DLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
291 CALL DLASSQ( M1, X1, INCX1, SCL1, SSQ1 )
292 NORMSQ2 = SCL1**2*SSQ1 + SCL2**2*SSQ2
294 * If second projection is sufficiently large in norm, then do
295 * nothing more. Alternatively, if it shrunk significantly, then
296 * truncate it to zero.
298 IF( NORMSQ2 .LT. ALPHASQ*NORMSQ1 ) THEN