LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sorbdb6.f
Go to the documentation of this file.
1*> \brief \b SORBDB6
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SORBDB6 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sorbdb6.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sorbdb6.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sorbdb6.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SORBDB6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1, Q2,
20* LDQ2, WORK, LWORK, INFO )
21*
22* .. Scalar Arguments ..
23* INTEGER INCX1, INCX2, INFO, LDQ1, LDQ2, LWORK, M1, M2,
24* $ N
25* ..
26* .. Array Arguments ..
27* REAL Q1(LDQ1,*), Q2(LDQ2,*), WORK(*), X1(*), X2(*)
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*>\verbatim
35*>
36*> SORBDB6 orthogonalizes the column vector
37*> X = [ X1 ]
38*> [ X2 ]
39*> with respect to the columns of
40*> Q = [ Q1 ] .
41*> [ Q2 ]
42*> The columns of Q must be orthonormal. The orthogonalized vector will
43*> be zero if and only if it lies entirely in the range of Q.
44*>
45*> The projection is computed with at most two iterations of the
46*> classical Gram-Schmidt algorithm, see
47*> * L. Giraud, J. Langou, M. Rozložník. "On the round-off error
48*> analysis of the Gram-Schmidt algorithm with reorthogonalization."
49*> 2002. CERFACS Technical Report No. TR/PA/02/33. URL:
50*> https://www.cerfacs.fr/algor/reports/2002/TR_PA_02_33.pdf
51*>
52*>\endverbatim
53*
54* Arguments:
55* ==========
56*
57*> \param[in] M1
58*> \verbatim
59*> M1 is INTEGER
60*> The dimension of X1 and the number of rows in Q1. 0 <= M1.
61*> \endverbatim
62*>
63*> \param[in] M2
64*> \verbatim
65*> M2 is INTEGER
66*> The dimension of X2 and the number of rows in Q2. 0 <= M2.
67*> \endverbatim
68*>
69*> \param[in] N
70*> \verbatim
71*> N is INTEGER
72*> The number of columns in Q1 and Q2. 0 <= N.
73*> \endverbatim
74*>
75*> \param[in,out] X1
76*> \verbatim
77*> X1 is REAL array, dimension (M1)
78*> On entry, the top part of the vector to be orthogonalized.
79*> On exit, the top part of the projected vector.
80*> \endverbatim
81*>
82*> \param[in] INCX1
83*> \verbatim
84*> INCX1 is INTEGER
85*> Increment for entries of X1.
86*> \endverbatim
87*>
88*> \param[in,out] X2
89*> \verbatim
90*> X2 is REAL array, dimension (M2)
91*> On entry, the bottom part of the vector to be
92*> orthogonalized. On exit, the bottom part of the projected
93*> vector.
94*> \endverbatim
95*>
96*> \param[in] INCX2
97*> \verbatim
98*> INCX2 is INTEGER
99*> Increment for entries of X2.
100*> \endverbatim
101*>
102*> \param[in] Q1
103*> \verbatim
104*> Q1 is REAL array, dimension (LDQ1, N)
105*> The top part of the orthonormal basis matrix.
106*> \endverbatim
107*>
108*> \param[in] LDQ1
109*> \verbatim
110*> LDQ1 is INTEGER
111*> The leading dimension of Q1. LDQ1 >= M1.
112*> \endverbatim
113*>
114*> \param[in] Q2
115*> \verbatim
116*> Q2 is REAL array, dimension (LDQ2, N)
117*> The bottom part of the orthonormal basis matrix.
118*> \endverbatim
119*>
120*> \param[in] LDQ2
121*> \verbatim
122*> LDQ2 is INTEGER
123*> The leading dimension of Q2. LDQ2 >= M2.
124*> \endverbatim
125*>
126*> \param[out] WORK
127*> \verbatim
128*> WORK is REAL array, dimension (LWORK)
129*> \endverbatim
130*>
131*> \param[in] LWORK
132*> \verbatim
133*> LWORK is INTEGER
134*> The dimension of the array WORK. LWORK >= N.
135*> \endverbatim
136*>
137*> \param[out] INFO
138*> \verbatim
139*> INFO is INTEGER
140*> = 0: successful exit.
141*> < 0: if INFO = -i, the i-th argument had an illegal value.
142*> \endverbatim
143*
144* Authors:
145* ========
146*
147*> \author Univ. of Tennessee
148*> \author Univ. of California Berkeley
149*> \author Univ. of Colorado Denver
150*> \author NAG Ltd.
151*
152*> \ingroup unbdb6
153*
154* =====================================================================
155 SUBROUTINE sorbdb6( M1, M2, N, X1, INCX1, X2, INCX2, Q1, LDQ1,
156 $ Q2,
157 $ LDQ2, WORK, LWORK, INFO )
158*
159* -- LAPACK computational routine --
160* -- LAPACK is a software package provided by Univ. of Tennessee, --
161* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162*
163* .. Scalar Arguments ..
164 INTEGER INCX1, INCX2, INFO, LDQ1, LDQ2, LWORK, M1, M2,
165 $ N
166* ..
167* .. Array Arguments ..
168 REAL Q1(LDQ1,*), Q2(LDQ2,*), WORK(*), X1(*), X2(*)
169* ..
170*
171* =====================================================================
172*
173* .. Parameters ..
174 REAL ALPHA, REALONE, REALZERO
175 PARAMETER ( ALPHA = 0.83e0, realone = 1.0e0,
176 $ realzero = 0.0e0 )
177 REAL NEGONE, ONE, ZERO
178 PARAMETER ( NEGONE = -1.0e0, one = 1.0e0, zero = 0.0e0 )
179* ..
180* .. Local Scalars ..
181 INTEGER I, IX
182 REAL EPS, NORM, NORM_NEW, SCL, SSQ
183* ..
184* .. External Functions ..
185 REAL SLAMCH
186* ..
187* .. External Subroutines ..
188 EXTERNAL sgemv, slassq, xerbla
189* ..
190* .. Intrinsic Function ..
191 INTRINSIC max
192* ..
193* .. Executable Statements ..
194*
195* Test input arguments
196*
197 info = 0
198 IF( m1 .LT. 0 ) THEN
199 info = -1
200 ELSE IF( m2 .LT. 0 ) THEN
201 info = -2
202 ELSE IF( n .LT. 0 ) THEN
203 info = -3
204 ELSE IF( incx1 .LT. 1 ) THEN
205 info = -5
206 ELSE IF( incx2 .LT. 1 ) THEN
207 info = -7
208 ELSE IF( ldq1 .LT. max( 1, m1 ) ) THEN
209 info = -9
210 ELSE IF( ldq2 .LT. max( 1, m2 ) ) THEN
211 info = -11
212 ELSE IF( lwork .LT. n ) THEN
213 info = -13
214 END IF
215*
216 IF( info .NE. 0 ) THEN
217 CALL xerbla( 'SORBDB6', -info )
218 RETURN
219 END IF
220*
221 eps = slamch( 'Precision' )
222*
223* Compute the Euclidean norm of X
224*
225 scl = realzero
226 ssq = realzero
227 CALL slassq( m1, x1, incx1, scl, ssq )
228 CALL slassq( m2, x2, incx2, scl, ssq )
229 norm = scl * sqrt( ssq )
230*
231* First, project X onto the orthogonal complement of Q's column
232* space
233*
234 IF( m1 .EQ. 0 ) THEN
235 DO i = 1, n
236 work(i) = zero
237 END DO
238 ELSE
239 CALL sgemv( 'C', m1, n, one, q1, ldq1, x1, incx1, zero,
240 $ work,
241 $ 1 )
242 END IF
243*
244 CALL sgemv( 'C', m2, n, one, q2, ldq2, x2, incx2, one, work,
245 $ 1 )
246*
247 CALL sgemv( 'N', m1, n, negone, q1, ldq1, work, 1, one, x1,
248 $ incx1 )
249 CALL sgemv( 'N', m2, n, negone, q2, ldq2, work, 1, one, x2,
250 $ incx2 )
251*
252 scl = realzero
253 ssq = realzero
254 CALL slassq( m1, x1, incx1, scl, ssq )
255 CALL slassq( m2, x2, incx2, scl, ssq )
256 norm_new = scl * sqrt(ssq)
257*
258* If projection is sufficiently large in norm, then stop.
259* If projection is zero, then stop.
260* Otherwise, project again.
261*
262 IF( norm_new .GE. alpha * norm ) THEN
263 RETURN
264 END IF
265*
266 IF( norm_new .LE. real( n ) * eps * norm ) THEN
267 DO ix = 1, 1 + (m1-1)*incx1, incx1
268 x1( ix ) = zero
269 END DO
270 DO ix = 1, 1 + (m2-1)*incx2, incx2
271 x2( ix ) = zero
272 END DO
273 RETURN
274 END IF
275*
276 norm = norm_new
277*
278 DO i = 1, n
279 work(i) = zero
280 END DO
281*
282 IF( m1 .EQ. 0 ) THEN
283 DO i = 1, n
284 work(i) = zero
285 END DO
286 ELSE
287 CALL sgemv( 'C', m1, n, one, q1, ldq1, x1, incx1, zero,
288 $ work,
289 $ 1 )
290 END IF
291*
292 CALL sgemv( 'C', m2, n, one, q2, ldq2, x2, incx2, one, work,
293 $ 1 )
294*
295 CALL sgemv( 'N', m1, n, negone, q1, ldq1, work, 1, one, x1,
296 $ incx1 )
297 CALL sgemv( 'N', m2, n, negone, q2, ldq2, work, 1, one, x2,
298 $ incx2 )
299*
300 scl = realzero
301 ssq = realzero
302 CALL slassq( m1, x1, incx1, scl, ssq )
303 CALL slassq( m2, x2, incx2, scl, ssq )
304 norm_new = scl * sqrt(ssq)
305*
306* If second projection is sufficiently large in norm, then do
307* nothing more. Alternatively, if it shrunk significantly, then
308* truncate it to zero.
309*
310 IF( norm_new .LT. alpha * norm ) THEN
311 DO ix = 1, 1 + (m1-1)*incx1, incx1
312 x1(ix) = zero
313 END DO
314 DO ix = 1, 1 + (m2-1)*incx2, incx2
315 x2(ix) = zero
316 END DO
317 END IF
318*
319 RETURN
320*
321* End of SORBDB6
322*
323 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
Definition sgemv.f:158
subroutine slassq(n, x, incx, scale, sumsq)
SLASSQ updates a sum of squares represented in scaled form.
Definition slassq.f90:122
subroutine sorbdb6(m1, m2, n, x1, incx1, x2, incx2, q1, ldq1, q2, ldq2, work, lwork, info)
SORBDB6
Definition sorbdb6.f:158