LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dtrexc.f
Go to the documentation of this file.
1*> \brief \b DTREXC
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DTREXC + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtrexc.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtrexc.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtrexc.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DTREXC( COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, WORK,
20* INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER COMPQ
24* INTEGER IFST, ILST, INFO, LDQ, LDT, N
25* ..
26* .. Array Arguments ..
27* DOUBLE PRECISION Q( LDQ, * ), T( LDT, * ), WORK( * )
28* ..
29*
30*
31*> \par Purpose:
32* =============
33*>
34*> \verbatim
35*>
36*> DTREXC reorders the real Schur factorization of a real matrix
37*> A = Q*T*Q**T, so that the diagonal block of T with row index IFST is
38*> moved to row ILST.
39*>
40*> The real Schur form T is reordered by an orthogonal similarity
41*> transformation Z**T*T*Z, and optionally the matrix Q of Schur vectors
42*> is updated by postmultiplying it with Z.
43*>
44*> T must be in Schur canonical form (as returned by DHSEQR), that is,
45*> block upper triangular with 1-by-1 and 2-by-2 diagonal blocks; each
46*> 2-by-2 diagonal block has its diagonal elements equal and its
47*> off-diagonal elements of opposite sign.
48*> \endverbatim
49*
50* Arguments:
51* ==========
52*
53*> \param[in] COMPQ
54*> \verbatim
55*> COMPQ is CHARACTER*1
56*> = 'V': update the matrix Q of Schur vectors;
57*> = 'N': do not update Q.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*> N is INTEGER
63*> The order of the matrix T. N >= 0.
64*> If N == 0 arguments ILST and IFST may be any value.
65*> \endverbatim
66*>
67*> \param[in,out] T
68*> \verbatim
69*> T is DOUBLE PRECISION array, dimension (LDT,N)
70*> On entry, the upper quasi-triangular matrix T, in Schur
71*> Schur canonical form.
72*> On exit, the reordered upper quasi-triangular matrix, again
73*> in Schur canonical form.
74*> \endverbatim
75*>
76*> \param[in] LDT
77*> \verbatim
78*> LDT is INTEGER
79*> The leading dimension of the array T. LDT >= max(1,N).
80*> \endverbatim
81*>
82*> \param[in,out] Q
83*> \verbatim
84*> Q is DOUBLE PRECISION array, dimension (LDQ,N)
85*> On entry, if COMPQ = 'V', the matrix Q of Schur vectors.
86*> On exit, if COMPQ = 'V', Q has been postmultiplied by the
87*> orthogonal transformation matrix Z which reorders T.
88*> If COMPQ = 'N', Q is not referenced.
89*> \endverbatim
90*>
91*> \param[in] LDQ
92*> \verbatim
93*> LDQ is INTEGER
94*> The leading dimension of the array Q. LDQ >= 1, and if
95*> COMPQ = 'V', LDQ >= max(1,N).
96*> \endverbatim
97*>
98*> \param[in,out] IFST
99*> \verbatim
100*> IFST is INTEGER
101*> \endverbatim
102*>
103*> \param[in,out] ILST
104*> \verbatim
105*> ILST is INTEGER
106*>
107*> Specify the reordering of the diagonal blocks of T.
108*> The block with row index IFST is moved to row ILST, by a
109*> sequence of transpositions between adjacent blocks.
110*> On exit, if IFST pointed on entry to the second row of a
111*> 2-by-2 block, it is changed to point to the first row; ILST
112*> always points to the first row of the block in its final
113*> position (which may differ from its input value by +1 or -1).
114*> 1 <= IFST <= N; 1 <= ILST <= N.
115*> \endverbatim
116*>
117*> \param[out] WORK
118*> \verbatim
119*> WORK is DOUBLE PRECISION array, dimension (N)
120*> \endverbatim
121*>
122*> \param[out] INFO
123*> \verbatim
124*> INFO is INTEGER
125*> = 0: successful exit
126*> < 0: if INFO = -i, the i-th argument had an illegal value
127*> = 1: two adjacent blocks were too close to swap (the problem
128*> is very ill-conditioned); T may have been partially
129*> reordered, and ILST points to the first row of the
130*> current position of the block being moved.
131*> \endverbatim
132*
133* Authors:
134* ========
135*
136*> \author Univ. of Tennessee
137*> \author Univ. of California Berkeley
138*> \author Univ. of Colorado Denver
139*> \author NAG Ltd.
140*
141*> \ingroup trexc
142*
143* =====================================================================
144 SUBROUTINE dtrexc( COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, WORK,
145 $ INFO )
146*
147* -- LAPACK computational routine --
148* -- LAPACK is a software package provided by Univ. of Tennessee, --
149* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
150*
151* .. Scalar Arguments ..
152 CHARACTER COMPQ
153 INTEGER IFST, ILST, INFO, LDQ, LDT, N
154* ..
155* .. Array Arguments ..
156 DOUBLE PRECISION Q( LDQ, * ), T( LDT, * ), WORK( * )
157* ..
158*
159* =====================================================================
160*
161* .. Parameters ..
162 DOUBLE PRECISION ZERO
163 parameter( zero = 0.0d+0 )
164* ..
165* .. Local Scalars ..
166 LOGICAL WANTQ
167 INTEGER HERE, NBF, NBL, NBNEXT
168* ..
169* .. External Functions ..
170 LOGICAL LSAME
171 EXTERNAL lsame
172* ..
173* .. External Subroutines ..
174 EXTERNAL dlaexc, xerbla
175* ..
176* .. Intrinsic Functions ..
177 INTRINSIC max
178* ..
179* .. Executable Statements ..
180*
181* Decode and test the input arguments.
182*
183 info = 0
184 wantq = lsame( compq, 'V' )
185 IF( .NOT.wantq .AND. .NOT.lsame( compq, 'N' ) ) THEN
186 info = -1
187 ELSE IF( n.LT.0 ) THEN
188 info = -2
189 ELSE IF( ldt.LT.max( 1, n ) ) THEN
190 info = -4
191 ELSE IF( ldq.LT.1 .OR. ( wantq .AND. ldq.LT.max( 1, n ) ) ) THEN
192 info = -6
193 ELSE IF(( ifst.LT.1 .OR. ifst.GT.n ).AND.( n.GT.0 )) THEN
194 info = -7
195 ELSE IF(( ilst.LT.1 .OR. ilst.GT.n ).AND.( n.GT.0 )) THEN
196 info = -8
197 END IF
198 IF( info.NE.0 ) THEN
199 CALL xerbla( 'DTREXC', -info )
200 RETURN
201 END IF
202*
203* Quick return if possible
204*
205 IF( n.LE.1 )
206 $ RETURN
207*
208* Determine the first row of specified block
209* and find out it is 1 by 1 or 2 by 2.
210*
211 IF( ifst.GT.1 ) THEN
212 IF( t( ifst, ifst-1 ).NE.zero )
213 $ ifst = ifst - 1
214 END IF
215 nbf = 1
216 IF( ifst.LT.n ) THEN
217 IF( t( ifst+1, ifst ).NE.zero )
218 $ nbf = 2
219 END IF
220*
221* Determine the first row of the final block
222* and find out it is 1 by 1 or 2 by 2.
223*
224 IF( ilst.GT.1 ) THEN
225 IF( t( ilst, ilst-1 ).NE.zero )
226 $ ilst = ilst - 1
227 END IF
228 nbl = 1
229 IF( ilst.LT.n ) THEN
230 IF( t( ilst+1, ilst ).NE.zero )
231 $ nbl = 2
232 END IF
233*
234 IF( ifst.EQ.ilst )
235 $ RETURN
236*
237 IF( ifst.LT.ilst ) THEN
238*
239* Update ILST
240*
241 IF( nbf.EQ.2 .AND. nbl.EQ.1 )
242 $ ilst = ilst - 1
243 IF( nbf.EQ.1 .AND. nbl.EQ.2 )
244 $ ilst = ilst + 1
245*
246 here = ifst
247*
248 10 CONTINUE
249*
250* Swap block with next one below
251*
252 IF( nbf.EQ.1 .OR. nbf.EQ.2 ) THEN
253*
254* Current block either 1 by 1 or 2 by 2
255*
256 nbnext = 1
257 IF( here+nbf+1.LE.n ) THEN
258 IF( t( here+nbf+1, here+nbf ).NE.zero )
259 $ nbnext = 2
260 END IF
261 CALL dlaexc( wantq, n, t, ldt, q, ldq, here, nbf, nbnext,
262 $ work, info )
263 IF( info.NE.0 ) THEN
264 ilst = here
265 RETURN
266 END IF
267 here = here + nbnext
268*
269* Test if 2 by 2 block breaks into two 1 by 1 blocks
270*
271 IF( nbf.EQ.2 ) THEN
272 IF( t( here+1, here ).EQ.zero )
273 $ nbf = 3
274 END IF
275*
276 ELSE
277*
278* Current block consists of two 1 by 1 blocks each of which
279* must be swapped individually
280*
281 nbnext = 1
282 IF( here+3.LE.n ) THEN
283 IF( t( here+3, here+2 ).NE.zero )
284 $ nbnext = 2
285 END IF
286 CALL dlaexc( wantq, n, t, ldt, q, ldq, here+1, 1, nbnext,
287 $ work, info )
288 IF( info.NE.0 ) THEN
289 ilst = here
290 RETURN
291 END IF
292 IF( nbnext.EQ.1 ) THEN
293*
294* Swap two 1 by 1 blocks, no problems possible
295*
296 CALL dlaexc( wantq, n, t, ldt, q, ldq, here, 1,
297 $ nbnext,
298 $ work, info )
299 here = here + 1
300 ELSE
301*
302* Recompute NBNEXT in case 2 by 2 split
303*
304 IF( t( here+2, here+1 ).EQ.zero )
305 $ nbnext = 1
306 IF( nbnext.EQ.2 ) THEN
307*
308* 2 by 2 Block did not split
309*
310 CALL dlaexc( wantq, n, t, ldt, q, ldq, here, 1,
311 $ nbnext, work, info )
312 IF( info.NE.0 ) THEN
313 ilst = here
314 RETURN
315 END IF
316 here = here + 2
317 ELSE
318*
319* 2 by 2 Block did split
320*
321 CALL dlaexc( wantq, n, t, ldt, q, ldq, here, 1, 1,
322 $ work, info )
323 CALL dlaexc( wantq, n, t, ldt, q, ldq, here+1, 1,
324 $ 1,
325 $ work, info )
326 here = here + 2
327 END IF
328 END IF
329 END IF
330 IF( here.LT.ilst )
331 $ GO TO 10
332*
333 ELSE
334*
335 here = ifst
336 20 CONTINUE
337*
338* Swap block with next one above
339*
340 IF( nbf.EQ.1 .OR. nbf.EQ.2 ) THEN
341*
342* Current block either 1 by 1 or 2 by 2
343*
344 nbnext = 1
345 IF( here.GE.3 ) THEN
346 IF( t( here-1, here-2 ).NE.zero )
347 $ nbnext = 2
348 END IF
349 CALL dlaexc( wantq, n, t, ldt, q, ldq, here-nbnext,
350 $ nbnext,
351 $ nbf, work, info )
352 IF( info.NE.0 ) THEN
353 ilst = here
354 RETURN
355 END IF
356 here = here - nbnext
357*
358* Test if 2 by 2 block breaks into two 1 by 1 blocks
359*
360 IF( nbf.EQ.2 ) THEN
361 IF( t( here+1, here ).EQ.zero )
362 $ nbf = 3
363 END IF
364*
365 ELSE
366*
367* Current block consists of two 1 by 1 blocks each of which
368* must be swapped individually
369*
370 nbnext = 1
371 IF( here.GE.3 ) THEN
372 IF( t( here-1, here-2 ).NE.zero )
373 $ nbnext = 2
374 END IF
375 CALL dlaexc( wantq, n, t, ldt, q, ldq, here-nbnext,
376 $ nbnext,
377 $ 1, work, info )
378 IF( info.NE.0 ) THEN
379 ilst = here
380 RETURN
381 END IF
382 IF( nbnext.EQ.1 ) THEN
383*
384* Swap two 1 by 1 blocks, no problems possible
385*
386 CALL dlaexc( wantq, n, t, ldt, q, ldq, here, nbnext,
387 $ 1,
388 $ work, info )
389 here = here - 1
390 ELSE
391*
392* Recompute NBNEXT in case 2 by 2 split
393*
394 IF( t( here, here-1 ).EQ.zero )
395 $ nbnext = 1
396 IF( nbnext.EQ.2 ) THEN
397*
398* 2 by 2 Block did not split
399*
400 CALL dlaexc( wantq, n, t, ldt, q, ldq, here-1, 2,
401 $ 1,
402 $ work, info )
403 IF( info.NE.0 ) THEN
404 ilst = here
405 RETURN
406 END IF
407 here = here - 2
408 ELSE
409*
410* 2 by 2 Block did split
411*
412 CALL dlaexc( wantq, n, t, ldt, q, ldq, here, 1, 1,
413 $ work, info )
414 CALL dlaexc( wantq, n, t, ldt, q, ldq, here-1, 1,
415 $ 1,
416 $ work, info )
417 here = here - 2
418 END IF
419 END IF
420 END IF
421 IF( here.GT.ilst )
422 $ GO TO 20
423 END IF
424 ilst = here
425*
426 RETURN
427*
428* End of DTREXC
429*
430 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dlaexc(wantq, n, t, ldt, q, ldq, j1, n1, n2, work, info)
DLAEXC swaps adjacent diagonal blocks of a real upper quasi-triangular matrix in Schur canonical form...
Definition dlaexc.f:136
subroutine dtrexc(compq, n, t, ldt, q, ldq, ifst, ilst, work, info)
DTREXC
Definition dtrexc.f:146