LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
sorbdb.f
Go to the documentation of this file.
1 *> \brief \b SORBDB
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download SORBDB + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sorbdb.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sorbdb.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sorbdb.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SORBDB( TRANS, SIGNS, M, P, Q, X11, LDX11, X12, LDX12,
22 * X21, LDX21, X22, LDX22, THETA, PHI, TAUP1,
23 * TAUP2, TAUQ1, TAUQ2, WORK, LWORK, INFO )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER SIGNS, TRANS
27 * INTEGER INFO, LDX11, LDX12, LDX21, LDX22, LWORK, M, P,
28 * $ Q
29 * ..
30 * .. Array Arguments ..
31 * REAL PHI( * ), THETA( * )
32 * REAL TAUP1( * ), TAUP2( * ), TAUQ1( * ), TAUQ2( * ),
33 * $ WORK( * ), X11( LDX11, * ), X12( LDX12, * ),
34 * $ X21( LDX21, * ), X22( LDX22, * )
35 * ..
36 *
37 *
38 *> \par Purpose:
39 * =============
40 *>
41 *> \verbatim
42 *>
43 *> SORBDB simultaneously bidiagonalizes the blocks of an M-by-M
44 *> partitioned orthogonal matrix X:
45 *>
46 *> [ B11 | B12 0 0 ]
47 *> [ X11 | X12 ] [ P1 | ] [ 0 | 0 -I 0 ] [ Q1 | ]**T
48 *> X = [-----------] = [---------] [----------------] [---------] .
49 *> [ X21 | X22 ] [ | P2 ] [ B21 | B22 0 0 ] [ | Q2 ]
50 *> [ 0 | 0 0 I ]
51 *>
52 *> X11 is P-by-Q. Q must be no larger than P, M-P, or M-Q. (If this is
53 *> not the case, then X must be transposed and/or permuted. This can be
54 *> done in constant time using the TRANS and SIGNS options. See SORCSD
55 *> for details.)
56 *>
57 *> The orthogonal matrices P1, P2, Q1, and Q2 are P-by-P, (M-P)-by-
58 *> (M-P), Q-by-Q, and (M-Q)-by-(M-Q), respectively. They are
59 *> represented implicitly by Householder vectors.
60 *>
61 *> B11, B12, B21, and B22 are Q-by-Q bidiagonal matrices represented
62 *> implicitly by angles THETA, PHI.
63 *> \endverbatim
64 *
65 * Arguments:
66 * ==========
67 *
68 *> \param[in] TRANS
69 *> \verbatim
70 *> TRANS is CHARACTER
71 *> = 'T': X, U1, U2, V1T, and V2T are stored in row-major
72 *> order;
73 *> otherwise: X, U1, U2, V1T, and V2T are stored in column-
74 *> major order.
75 *> \endverbatim
76 *>
77 *> \param[in] SIGNS
78 *> \verbatim
79 *> SIGNS is CHARACTER
80 *> = 'O': The lower-left block is made nonpositive (the
81 *> "other" convention);
82 *> otherwise: The upper-right block is made nonpositive (the
83 *> "default" convention).
84 *> \endverbatim
85 *>
86 *> \param[in] M
87 *> \verbatim
88 *> M is INTEGER
89 *> The number of rows and columns in X.
90 *> \endverbatim
91 *>
92 *> \param[in] P
93 *> \verbatim
94 *> P is INTEGER
95 *> The number of rows in X11 and X12. 0 <= P <= M.
96 *> \endverbatim
97 *>
98 *> \param[in] Q
99 *> \verbatim
100 *> Q is INTEGER
101 *> The number of columns in X11 and X21. 0 <= Q <=
102 *> MIN(P,M-P,M-Q).
103 *> \endverbatim
104 *>
105 *> \param[in,out] X11
106 *> \verbatim
107 *> X11 is REAL array, dimension (LDX11,Q)
108 *> On entry, the top-left block of the orthogonal matrix to be
109 *> reduced. On exit, the form depends on TRANS:
110 *> If TRANS = 'N', then
111 *> the columns of tril(X11) specify reflectors for P1,
112 *> the rows of triu(X11,1) specify reflectors for Q1;
113 *> else TRANS = 'T', and
114 *> the rows of triu(X11) specify reflectors for P1,
115 *> the columns of tril(X11,-1) specify reflectors for Q1.
116 *> \endverbatim
117 *>
118 *> \param[in] LDX11
119 *> \verbatim
120 *> LDX11 is INTEGER
121 *> The leading dimension of X11. If TRANS = 'N', then LDX11 >=
122 *> P; else LDX11 >= Q.
123 *> \endverbatim
124 *>
125 *> \param[in,out] X12
126 *> \verbatim
127 *> X12 is REAL array, dimension (LDX12,M-Q)
128 *> On entry, the top-right block of the orthogonal matrix to
129 *> be reduced. On exit, the form depends on TRANS:
130 *> If TRANS = 'N', then
131 *> the rows of triu(X12) specify the first P reflectors for
132 *> Q2;
133 *> else TRANS = 'T', and
134 *> the columns of tril(X12) specify the first P reflectors
135 *> for Q2.
136 *> \endverbatim
137 *>
138 *> \param[in] LDX12
139 *> \verbatim
140 *> LDX12 is INTEGER
141 *> The leading dimension of X12. If TRANS = 'N', then LDX12 >=
142 *> P; else LDX11 >= M-Q.
143 *> \endverbatim
144 *>
145 *> \param[in,out] X21
146 *> \verbatim
147 *> X21 is REAL array, dimension (LDX21,Q)
148 *> On entry, the bottom-left block of the orthogonal matrix to
149 *> be reduced. On exit, the form depends on TRANS:
150 *> If TRANS = 'N', then
151 *> the columns of tril(X21) specify reflectors for P2;
152 *> else TRANS = 'T', and
153 *> the rows of triu(X21) specify reflectors for P2.
154 *> \endverbatim
155 *>
156 *> \param[in] LDX21
157 *> \verbatim
158 *> LDX21 is INTEGER
159 *> The leading dimension of X21. If TRANS = 'N', then LDX21 >=
160 *> M-P; else LDX21 >= Q.
161 *> \endverbatim
162 *>
163 *> \param[in,out] X22
164 *> \verbatim
165 *> X22 is REAL array, dimension (LDX22,M-Q)
166 *> On entry, the bottom-right block of the orthogonal matrix to
167 *> be reduced. On exit, the form depends on TRANS:
168 *> If TRANS = 'N', then
169 *> the rows of triu(X22(Q+1:M-P,P+1:M-Q)) specify the last
170 *> M-P-Q reflectors for Q2,
171 *> else TRANS = 'T', and
172 *> the columns of tril(X22(P+1:M-Q,Q+1:M-P)) specify the last
173 *> M-P-Q reflectors for P2.
174 *> \endverbatim
175 *>
176 *> \param[in] LDX22
177 *> \verbatim
178 *> LDX22 is INTEGER
179 *> The leading dimension of X22. If TRANS = 'N', then LDX22 >=
180 *> M-P; else LDX22 >= M-Q.
181 *> \endverbatim
182 *>
183 *> \param[out] THETA
184 *> \verbatim
185 *> THETA is REAL array, dimension (Q)
186 *> The entries of the bidiagonal blocks B11, B12, B21, B22 can
187 *> be computed from the angles THETA and PHI. See Further
188 *> Details.
189 *> \endverbatim
190 *>
191 *> \param[out] PHI
192 *> \verbatim
193 *> PHI is REAL array, dimension (Q-1)
194 *> The entries of the bidiagonal blocks B11, B12, B21, B22 can
195 *> be computed from the angles THETA and PHI. See Further
196 *> Details.
197 *> \endverbatim
198 *>
199 *> \param[out] TAUP1
200 *> \verbatim
201 *> TAUP1 is REAL array, dimension (P)
202 *> The scalar factors of the elementary reflectors that define
203 *> P1.
204 *> \endverbatim
205 *>
206 *> \param[out] TAUP2
207 *> \verbatim
208 *> TAUP2 is REAL array, dimension (M-P)
209 *> The scalar factors of the elementary reflectors that define
210 *> P2.
211 *> \endverbatim
212 *>
213 *> \param[out] TAUQ1
214 *> \verbatim
215 *> TAUQ1 is REAL array, dimension (Q)
216 *> The scalar factors of the elementary reflectors that define
217 *> Q1.
218 *> \endverbatim
219 *>
220 *> \param[out] TAUQ2
221 *> \verbatim
222 *> TAUQ2 is REAL array, dimension (M-Q)
223 *> The scalar factors of the elementary reflectors that define
224 *> Q2.
225 *> \endverbatim
226 *>
227 *> \param[out] WORK
228 *> \verbatim
229 *> WORK is REAL array, dimension (LWORK)
230 *> \endverbatim
231 *>
232 *> \param[in] LWORK
233 *> \verbatim
234 *> LWORK is INTEGER
235 *> The dimension of the array WORK. LWORK >= M-Q.
236 *>
237 *> If LWORK = -1, then a workspace query is assumed; the routine
238 *> only calculates the optimal size of the WORK array, returns
239 *> this value as the first entry of the WORK array, and no error
240 *> message related to LWORK is issued by XERBLA.
241 *> \endverbatim
242 *>
243 *> \param[out] INFO
244 *> \verbatim
245 *> INFO is INTEGER
246 *> = 0: successful exit.
247 *> < 0: if INFO = -i, the i-th argument had an illegal value.
248 *> \endverbatim
249 *
250 * Authors:
251 * ========
252 *
253 *> \author Univ. of Tennessee
254 *> \author Univ. of California Berkeley
255 *> \author Univ. of Colorado Denver
256 *> \author NAG Ltd.
257 *
258 *> \date November 2011
259 *
260 *> \ingroup realOTHERcomputational
261 *
262 *> \par Further Details:
263 * =====================
264 *>
265 *> \verbatim
266 *>
267 *> The bidiagonal blocks B11, B12, B21, and B22 are represented
268 *> implicitly by angles THETA(1), ..., THETA(Q) and PHI(1), ...,
269 *> PHI(Q-1). B11 and B21 are upper bidiagonal, while B21 and B22 are
270 *> lower bidiagonal. Every entry in each bidiagonal band is a product
271 *> of a sine or cosine of a THETA with a sine or cosine of a PHI. See
272 *> [1] or SORCSD for details.
273 *>
274 *> P1, P2, Q1, and Q2 are represented as products of elementary
275 *> reflectors. See SORCSD for details on generating P1, P2, Q1, and Q2
276 *> using SORGQR and SORGLQ.
277 *> \endverbatim
278 *
279 *> \par References:
280 * ================
281 *>
282 *> [1] Brian D. Sutton. Computing the complete CS decomposition. Numer.
283 *> Algorithms, 50(1):33-65, 2009.
284 *>
285 * =====================================================================
286  SUBROUTINE sorbdb( TRANS, SIGNS, M, P, Q, X11, LDX11, X12, LDX12,
287  $ x21, ldx21, x22, ldx22, theta, phi, taup1,
288  $ taup2, tauq1, tauq2, work, lwork, info )
289 *
290 * -- LAPACK computational routine (version 3.4.0) --
291 * -- LAPACK is a software package provided by Univ. of Tennessee, --
292 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
293 * November 2011
294 *
295 * .. Scalar Arguments ..
296  CHARACTER signs, trans
297  INTEGER info, ldx11, ldx12, ldx21, ldx22, lwork, m, p,
298  $ q
299 * ..
300 * .. Array Arguments ..
301  REAL phi( * ), theta( * )
302  REAL taup1( * ), taup2( * ), tauq1( * ), tauq2( * ),
303  $ work( * ), x11( ldx11, * ), x12( ldx12, * ),
304  $ x21( ldx21, * ), x22( ldx22, * )
305 * ..
306 *
307 * ====================================================================
308 *
309 * .. Parameters ..
310  REAL realone
311  parameter( realone = 1.0e0 )
312  REAL one
313  parameter( one = 1.0e0 )
314 * ..
315 * .. Local Scalars ..
316  LOGICAL colmajor, lquery
317  INTEGER i, lworkmin, lworkopt
318  REAL z1, z2, z3, z4
319 * ..
320 * .. External Subroutines ..
321  EXTERNAL saxpy, slarf, slarfgp, sscal, xerbla
322 * ..
323 * .. External Functions ..
324  REAL snrm2
325  LOGICAL lsame
326  EXTERNAL snrm2, lsame
327 * ..
328 * .. Intrinsic Functions
329  INTRINSIC atan2, cos, max, sin
330 * ..
331 * .. Executable Statements ..
332 *
333 * Test input arguments
334 *
335  info = 0
336  colmajor = .NOT. lsame( trans, 'T' )
337  IF( .NOT. lsame( signs, 'O' ) ) THEN
338  z1 = realone
339  z2 = realone
340  z3 = realone
341  z4 = realone
342  ELSE
343  z1 = realone
344  z2 = -realone
345  z3 = realone
346  z4 = -realone
347  END IF
348  lquery = lwork .EQ. -1
349 *
350  IF( m .LT. 0 ) THEN
351  info = -3
352  ELSE IF( p .LT. 0 .OR. p .GT. m ) THEN
353  info = -4
354  ELSE IF( q .LT. 0 .OR. q .GT. p .OR. q .GT. m-p .OR.
355  $ q .GT. m-q ) THEN
356  info = -5
357  ELSE IF( colmajor .AND. ldx11 .LT. max( 1, p ) ) THEN
358  info = -7
359  ELSE IF( .NOT.colmajor .AND. ldx11 .LT. max( 1, q ) ) THEN
360  info = -7
361  ELSE IF( colmajor .AND. ldx12 .LT. max( 1, p ) ) THEN
362  info = -9
363  ELSE IF( .NOT.colmajor .AND. ldx12 .LT. max( 1, m-q ) ) THEN
364  info = -9
365  ELSE IF( colmajor .AND. ldx21 .LT. max( 1, m-p ) ) THEN
366  info = -11
367  ELSE IF( .NOT.colmajor .AND. ldx21 .LT. max( 1, q ) ) THEN
368  info = -11
369  ELSE IF( colmajor .AND. ldx22 .LT. max( 1, m-p ) ) THEN
370  info = -13
371  ELSE IF( .NOT.colmajor .AND. ldx22 .LT. max( 1, m-q ) ) THEN
372  info = -13
373  END IF
374 *
375 * Compute workspace
376 *
377  IF( info .EQ. 0 ) THEN
378  lworkopt = m - q
379  lworkmin = m - q
380  work(1) = lworkopt
381  IF( lwork .LT. lworkmin .AND. .NOT. lquery ) THEN
382  info = -21
383  END IF
384  END IF
385  IF( info .NE. 0 ) THEN
386  CALL xerbla( 'xORBDB', -info )
387  return
388  ELSE IF( lquery ) THEN
389  return
390  END IF
391 *
392 * Handle column-major and row-major separately
393 *
394  IF( colmajor ) THEN
395 *
396 * Reduce columns 1, ..., Q of X11, X12, X21, and X22
397 *
398  DO i = 1, q
399 *
400  IF( i .EQ. 1 ) THEN
401  CALL sscal( p-i+1, z1, x11(i,i), 1 )
402  ELSE
403  CALL sscal( p-i+1, z1*cos(phi(i-1)), x11(i,i), 1 )
404  CALL saxpy( p-i+1, -z1*z3*z4*sin(phi(i-1)), x12(i,i-1),
405  $ 1, x11(i,i), 1 )
406  END IF
407  IF( i .EQ. 1 ) THEN
408  CALL sscal( m-p-i+1, z2, x21(i,i), 1 )
409  ELSE
410  CALL sscal( m-p-i+1, z2*cos(phi(i-1)), x21(i,i), 1 )
411  CALL saxpy( m-p-i+1, -z2*z3*z4*sin(phi(i-1)), x22(i,i-1),
412  $ 1, x21(i,i), 1 )
413  END IF
414 *
415  theta(i) = atan2( snrm2( m-p-i+1, x21(i,i), 1 ),
416  $ snrm2( p-i+1, x11(i,i), 1 ) )
417 *
418  CALL slarfgp( p-i+1, x11(i,i), x11(i+1,i), 1, taup1(i) )
419  x11(i,i) = one
420  CALL slarfgp( m-p-i+1, x21(i,i), x21(i+1,i), 1, taup2(i) )
421  x21(i,i) = one
422 *
423  CALL slarf( 'L', p-i+1, q-i, x11(i,i), 1, taup1(i),
424  $ x11(i,i+1), ldx11, work )
425  CALL slarf( 'L', p-i+1, m-q-i+1, x11(i,i), 1, taup1(i),
426  $ x12(i,i), ldx12, work )
427  CALL slarf( 'L', m-p-i+1, q-i, x21(i,i), 1, taup2(i),
428  $ x21(i,i+1), ldx21, work )
429  CALL slarf( 'L', m-p-i+1, m-q-i+1, x21(i,i), 1, taup2(i),
430  $ x22(i,i), ldx22, work )
431 *
432  IF( i .LT. q ) THEN
433  CALL sscal( q-i, -z1*z3*sin(theta(i)), x11(i,i+1),
434  $ ldx11 )
435  CALL saxpy( q-i, z2*z3*cos(theta(i)), x21(i,i+1), ldx21,
436  $ x11(i,i+1), ldx11 )
437  END IF
438  CALL sscal( m-q-i+1, -z1*z4*sin(theta(i)), x12(i,i), ldx12 )
439  CALL saxpy( m-q-i+1, z2*z4*cos(theta(i)), x22(i,i), ldx22,
440  $ x12(i,i), ldx12 )
441 *
442  IF( i .LT. q )
443  $ phi(i) = atan2( snrm2( q-i, x11(i,i+1), ldx11 ),
444  $ snrm2( m-q-i+1, x12(i,i), ldx12 ) )
445 *
446  IF( i .LT. q ) THEN
447  CALL slarfgp( q-i, x11(i,i+1), x11(i,i+2), ldx11,
448  $ tauq1(i) )
449  x11(i,i+1) = one
450  END IF
451  CALL slarfgp( m-q-i+1, x12(i,i), x12(i,i+1), ldx12,
452  $ tauq2(i) )
453  x12(i,i) = one
454 *
455  IF( i .LT. q ) THEN
456  CALL slarf( 'R', p-i, q-i, x11(i,i+1), ldx11, tauq1(i),
457  $ x11(i+1,i+1), ldx11, work )
458  CALL slarf( 'R', m-p-i, q-i, x11(i,i+1), ldx11, tauq1(i),
459  $ x21(i+1,i+1), ldx21, work )
460  END IF
461  CALL slarf( 'R', p-i, m-q-i+1, x12(i,i), ldx12, tauq2(i),
462  $ x12(i+1,i), ldx12, work )
463  CALL slarf( 'R', m-p-i, m-q-i+1, x12(i,i), ldx12, tauq2(i),
464  $ x22(i+1,i), ldx22, work )
465 *
466  END DO
467 *
468 * Reduce columns Q + 1, ..., P of X12, X22
469 *
470  DO i = q + 1, p
471 *
472  CALL sscal( m-q-i+1, -z1*z4, x12(i,i), ldx12 )
473  CALL slarfgp( m-q-i+1, x12(i,i), x12(i,i+1), ldx12,
474  $ tauq2(i) )
475  x12(i,i) = one
476 *
477  CALL slarf( 'R', p-i, m-q-i+1, x12(i,i), ldx12, tauq2(i),
478  $ x12(i+1,i), ldx12, work )
479  IF( m-p-q .GE. 1 )
480  $ CALL slarf( 'R', m-p-q, m-q-i+1, x12(i,i), ldx12,
481  $ tauq2(i), x22(q+1,i), ldx22, work )
482 *
483  END DO
484 *
485 * Reduce columns P + 1, ..., M - Q of X12, X22
486 *
487  DO i = 1, m - p - q
488 *
489  CALL sscal( m-p-q-i+1, z2*z4, x22(q+i,p+i), ldx22 )
490  CALL slarfgp( m-p-q-i+1, x22(q+i,p+i), x22(q+i,p+i+1),
491  $ ldx22, tauq2(p+i) )
492  x22(q+i,p+i) = one
493  CALL slarf( 'R', m-p-q-i, m-p-q-i+1, x22(q+i,p+i), ldx22,
494  $ tauq2(p+i), x22(q+i+1,p+i), ldx22, work )
495 *
496  END DO
497 *
498  ELSE
499 *
500 * Reduce columns 1, ..., Q of X11, X12, X21, X22
501 *
502  DO i = 1, q
503 *
504  IF( i .EQ. 1 ) THEN
505  CALL sscal( p-i+1, z1, x11(i,i), ldx11 )
506  ELSE
507  CALL sscal( p-i+1, z1*cos(phi(i-1)), x11(i,i), ldx11 )
508  CALL saxpy( p-i+1, -z1*z3*z4*sin(phi(i-1)), x12(i-1,i),
509  $ ldx12, x11(i,i), ldx11 )
510  END IF
511  IF( i .EQ. 1 ) THEN
512  CALL sscal( m-p-i+1, z2, x21(i,i), ldx21 )
513  ELSE
514  CALL sscal( m-p-i+1, z2*cos(phi(i-1)), x21(i,i), ldx21 )
515  CALL saxpy( m-p-i+1, -z2*z3*z4*sin(phi(i-1)), x22(i-1,i),
516  $ ldx22, x21(i,i), ldx21 )
517  END IF
518 *
519  theta(i) = atan2( snrm2( m-p-i+1, x21(i,i), ldx21 ),
520  $ snrm2( p-i+1, x11(i,i), ldx11 ) )
521 *
522  CALL slarfgp( p-i+1, x11(i,i), x11(i,i+1), ldx11, taup1(i) )
523  x11(i,i) = one
524  CALL slarfgp( m-p-i+1, x21(i,i), x21(i,i+1), ldx21,
525  $ taup2(i) )
526  x21(i,i) = one
527 *
528  CALL slarf( 'R', q-i, p-i+1, x11(i,i), ldx11, taup1(i),
529  $ x11(i+1,i), ldx11, work )
530  CALL slarf( 'R', m-q-i+1, p-i+1, x11(i,i), ldx11, taup1(i),
531  $ x12(i,i), ldx12, work )
532  CALL slarf( 'R', q-i, m-p-i+1, x21(i,i), ldx21, taup2(i),
533  $ x21(i+1,i), ldx21, work )
534  CALL slarf( 'R', m-q-i+1, m-p-i+1, x21(i,i), ldx21,
535  $ taup2(i), x22(i,i), ldx22, work )
536 *
537  IF( i .LT. q ) THEN
538  CALL sscal( q-i, -z1*z3*sin(theta(i)), x11(i+1,i), 1 )
539  CALL saxpy( q-i, z2*z3*cos(theta(i)), x21(i+1,i), 1,
540  $ x11(i+1,i), 1 )
541  END IF
542  CALL sscal( m-q-i+1, -z1*z4*sin(theta(i)), x12(i,i), 1 )
543  CALL saxpy( m-q-i+1, z2*z4*cos(theta(i)), x22(i,i), 1,
544  $ x12(i,i), 1 )
545 *
546  IF( i .LT. q )
547  $ phi(i) = atan2( snrm2( q-i, x11(i+1,i), 1 ),
548  $ snrm2( m-q-i+1, x12(i,i), 1 ) )
549 *
550  IF( i .LT. q ) THEN
551  CALL slarfgp( q-i, x11(i+1,i), x11(i+2,i), 1, tauq1(i) )
552  x11(i+1,i) = one
553  END IF
554  CALL slarfgp( m-q-i+1, x12(i,i), x12(i+1,i), 1, tauq2(i) )
555  x12(i,i) = one
556 *
557  IF( i .LT. q ) THEN
558  CALL slarf( 'L', q-i, p-i, x11(i+1,i), 1, tauq1(i),
559  $ x11(i+1,i+1), ldx11, work )
560  CALL slarf( 'L', q-i, m-p-i, x11(i+1,i), 1, tauq1(i),
561  $ x21(i+1,i+1), ldx21, work )
562  END IF
563  CALL slarf( 'L', m-q-i+1, p-i, x12(i,i), 1, tauq2(i),
564  $ x12(i,i+1), ldx12, work )
565  CALL slarf( 'L', m-q-i+1, m-p-i, x12(i,i), 1, tauq2(i),
566  $ x22(i,i+1), ldx22, work )
567 *
568  END DO
569 *
570 * Reduce columns Q + 1, ..., P of X12, X22
571 *
572  DO i = q + 1, p
573 *
574  CALL sscal( m-q-i+1, -z1*z4, x12(i,i), 1 )
575  CALL slarfgp( m-q-i+1, x12(i,i), x12(i+1,i), 1, tauq2(i) )
576  x12(i,i) = one
577 *
578  CALL slarf( 'L', m-q-i+1, p-i, x12(i,i), 1, tauq2(i),
579  $ x12(i,i+1), ldx12, work )
580  IF( m-p-q .GE. 1 )
581  $ CALL slarf( 'L', m-q-i+1, m-p-q, x12(i,i), 1, tauq2(i),
582  $ x22(i,q+1), ldx22, work )
583 *
584  END DO
585 *
586 * Reduce columns P + 1, ..., M - Q of X12, X22
587 *
588  DO i = 1, m - p - q
589 *
590  CALL sscal( m-p-q-i+1, z2*z4, x22(p+i,q+i), 1 )
591  CALL slarfgp( m-p-q-i+1, x22(p+i,q+i), x22(p+i+1,q+i), 1,
592  $ tauq2(p+i) )
593  x22(p+i,q+i) = one
594 *
595  CALL slarf( 'L', m-p-q-i+1, m-p-q-i, x22(p+i,q+i), 1,
596  $ tauq2(p+i), x22(p+i,q+i+1), ldx22, work )
597 *
598  END DO
599 *
600  END IF
601 *
602  return
603 *
604 * End of SORBDB
605 *
606  END
607