1      SUBROUTINE DTGEXC( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
2     $                   LDZ, IFST, ILST, WORK, LWORK, INFO )
3*
4*  -- LAPACK routine (version 3.0) --
5*     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
6*     Courant Institute, Argonne National Lab, and Rice University
7*     June 30, 1999
8*
9*     .. Scalar Arguments ..
10      LOGICAL            WANTQ, WANTZ
11      INTEGER            IFST, ILST, INFO, LDA, LDB, LDQ, LDZ, LWORK, N
12*     ..
13*     .. Array Arguments ..
14      DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
15     $                   WORK( * ), Z( LDZ, * )
16*     ..
17*
18*  Purpose
19*  =======
20*
21*  DTGEXC reorders the generalized real Schur decomposition of a real
22*  matrix pair (A,B) using an orthogonal equivalence transformation
23*
24*                 (A, B) = Q * (A, B) * Z',
25*
26*  so that the diagonal block of (A, B) with row index IFST is moved
27*  to row ILST.
28*
29*  (A, B) must be in generalized real Schur canonical form (as returned
30*  by DGGES), i.e. A is block upper triangular with 1-by-1 and 2-by-2
31*  diagonal blocks. B is upper triangular.
32*
33*  Optionally, the matrices Q and Z of generalized Schur vectors are
34*  updated.
35*
36*         Q(in) * A(in) * Z(in)' = Q(out) * A(out) * Z(out)'
37*         Q(in) * B(in) * Z(in)' = Q(out) * B(out) * Z(out)'
38*
39*
40*  Arguments
41*  =========
42*
43*  WANTQ   (input) LOGICAL
44*          .TRUE. : update the left transformation matrix Q;
45*          .FALSE.: do not update Q.
46*
47*  WANTZ   (input) LOGICAL
48*          .TRUE. : update the right transformation matrix Z;
49*          .FALSE.: do not update Z.
50*
51*  N       (input) INTEGER
52*          The order of the matrices A and B. N >= 0.
53*
54*  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
55*          On entry, the matrix A in generalized real Schur canonical
56*          form.
57*          On exit, the updated matrix A, again in generalized
58*          real Schur canonical form.
59*
60*  LDA     (input)  INTEGER
61*          The leading dimension of the array A. LDA >= max(1,N).
62*
63*  B       (input/output) DOUBLE PRECISION array, dimension (LDB,N)
64*          On entry, the matrix B in generalized real Schur canonical
65*          form (A,B).
66*          On exit, the updated matrix B, again in generalized
67*          real Schur canonical form (A,B).
68*
69*  LDB     (input)  INTEGER
70*          The leading dimension of the array B. LDB >= max(1,N).
71*
72*  Q       (input/output) DOUBLE PRECISION array, dimension (LDZ,N)
73*          On entry, if WANTQ = .TRUE., the orthogonal matrix Q.
74*          On exit, the updated matrix Q.
75*          If WANTQ = .FALSE., Q is not referenced.
76*
77*  LDQ     (input) INTEGER
78*          The leading dimension of the array Q. LDQ >= 1.
79*          If WANTQ = .TRUE., LDQ >= N.
80*
81*  Z       (input/output) DOUBLE PRECISION array, dimension (LDZ,N)
82*          On entry, if WANTZ = .TRUE., the orthogonal matrix Z.
83*          On exit, the updated matrix Z.
84*          If WANTZ = .FALSE., Z is not referenced.
85*
86*  LDZ     (input) INTEGER
87*          The leading dimension of the array Z. LDZ >= 1.
88*          If WANTZ = .TRUE., LDZ >= N.
89*
90*  IFST    (input/output) INTEGER
91*  ILST    (input/output) INTEGER
92*          Specify the reordering of the diagonal blocks of (A, B).
93*          The block with row index IFST is moved to row ILST, by a
94*          sequence of swapping between adjacent blocks.
95*          On exit, if IFST pointed on entry to the second row of
96*          a 2-by-2 block, it is changed to point to the first row;
97*          ILST always points to the first row of the block in its
98*          final position (which may differ from its input value by
99*          +1 or -1). 1 <= IFST, ILST <= N.
100*
101*  WORK    (workspace/output) DOUBLE PRECISION array, dimension (LWORK)
102*          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
103*
104*  LWORK   (input) INTEGER
105*          The dimension of the array WORK. LWORK >= 4*N + 16.
106*
107*          If LWORK = -1, then a workspace query is assumed; the routine
108*          only calculates the optimal size of the WORK array, returns
109*          this value as the first entry of the WORK array, and no error
110*          message related to LWORK is issued by XERBLA.
111*
112*  INFO    (output) INTEGER
113*           =0:  successful exit.
114*           <0:  if INFO = -i, the i-th argument had an illegal value.
115*           =1:  The transformed matrix pair (A, B) would be too far
116*                from generalized Schur form; the problem is ill-
117*                conditioned. (A, B) may have been partially reordered,
118*                and ILST points to the first row of the current
119*                position of the block being moved.
120*
121*  Further Details
122*  ===============
123*
124*  Based on contributions by
125*     Bo Kagstrom and Peter Poromaa, Department of Computing Science,
126*     Umea University, S-901 87 Umea, Sweden.
127*
128*  [1] B. Kagstrom; A Direct Method for Reordering Eigenvalues in the
129*      Generalized Real Schur Form of a Regular Matrix Pair (A, B), in
130*      M.S. Moonen et al (eds), Linear Algebra for Large Scale and
131*      Real-Time Applications, Kluwer Academic Publ. 1993, pp 195-218.
132*
133*  =====================================================================
134*
135*     .. Parameters ..
136      DOUBLE PRECISION   ZERO
137      PARAMETER          ( ZERO = 0.0D+0 )
138*     ..
139*     .. Local Scalars ..
140      LOGICAL            LQUERY
141      INTEGER            HERE, LWMIN, NBF, NBL, NBNEXT
142*     ..
143*     .. External Subroutines ..
144      EXTERNAL           DTGEX2, XERBLA
145*     ..
146*     .. Intrinsic Functions ..
147      INTRINSIC          MAX
148*     ..
149*     .. Executable Statements ..
150*
151*     Decode and test input arguments.
152*
153      INFO = 0
154      LWMIN = MAX( 1, 4*N+16 )
155      LQUERY = ( LWORK.EQ.-1 )
156      IF( N.LT.0 ) THEN
157         INFO = -3
158      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
159         INFO = -5
160      ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
161         INFO = -7
162      ELSE IF( LDQ.LT.1 .OR. WANTQ .AND. ( LDQ.LT.MAX( 1, N ) ) ) THEN
163         INFO = -9
164      ELSE IF( LDZ.LT.1 .OR. WANTZ .AND. ( LDZ.LT.MAX( 1, N ) ) ) THEN
165         INFO = -11
166      ELSE IF( IFST.LT.1 .OR. IFST.GT.N ) THEN
167         INFO = -12
168      ELSE IF( ILST.LT.1 .OR. ILST.GT.N ) THEN
169         INFO = -13
170      ELSE IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
171         INFO = -15
172      END IF
173*
174      IF( INFO.EQ.0 ) THEN
175         WORK( 1 ) = LWMIN
176      END IF
177*
178      IF( INFO.NE.0 ) THEN
179         CALL XERBLA( 'DTGEXC', -INFO )
180         RETURN
181      ELSE IF( LQUERY ) THEN
182         RETURN
183      END IF
184*
185*     Quick return if possible
186*
187      IF( N.LE.1 )
188     $   RETURN
189*
190*     Determine the first row of the specified block and find out
191*     if it is 1-by-1 or 2-by-2.
192*
193      IF( IFST.GT.1 ) THEN
194         IF( A( IFST, IFST-1 ).NE.ZERO )
195     $      IFST = IFST - 1
196      END IF
197      NBF = 1
198      IF( IFST.LT.N ) THEN
199         IF( A( IFST+1, IFST ).NE.ZERO )
200     $      NBF = 2
201      END IF
202*
203*     Determine the first row of the final block
204*     and find out if it is 1-by-1 or 2-by-2.
205*
206      IF( ILST.GT.1 ) THEN
207         IF( A( ILST, ILST-1 ).NE.ZERO )
208     $      ILST = ILST - 1
209      END IF
210      NBL = 1
211      IF( ILST.LT.N ) THEN
212         IF( A( ILST+1, ILST ).NE.ZERO )
213     $      NBL = 2
214      END IF
215      IF( IFST.EQ.ILST )
216     $   RETURN
217*
218      IF( IFST.LT.ILST ) THEN
219*
220*        Update ILST.
221*
222         IF( NBF.EQ.2 .AND. NBL.EQ.1 )
223     $      ILST = ILST - 1
224         IF( NBF.EQ.1 .AND. NBL.EQ.2 )
225     $      ILST = ILST + 1
226*
227         HERE = IFST
228*
229   10    CONTINUE
230*
231*        Swap with next one below.
232*
233         IF( NBF.EQ.1 .OR. NBF.EQ.2 ) THEN
234*
235*           Current block either 1-by-1 or 2-by-2.
236*
237            NBNEXT = 1
238            IF( HERE+NBF+1.LE.N ) THEN
239               IF( A( HERE+NBF+1, HERE+NBF ).NE.ZERO )
240     $            NBNEXT = 2
241            END IF
242            CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
243     $                   LDZ, HERE, NBF, NBNEXT, WORK, LWORK, INFO )
244            IF( INFO.NE.0 ) THEN
245               ILST = HERE
246               RETURN
247            END IF
248            HERE = HERE + NBNEXT
249*
250*           Test if 2-by-2 block breaks into two 1-by-1 blocks.
251*
252            IF( NBF.EQ.2 ) THEN
253               IF( A( HERE+1, HERE ).EQ.ZERO )
254     $            NBF = 3
255            END IF
256*
257         ELSE
258*
259*           Current block consists of two 1-by-1 blocks, each of which
260*           must be swapped individually.
261*
262            NBNEXT = 1
263            IF( HERE+3.LE.N ) THEN
264               IF( A( HERE+3, HERE+2 ).NE.ZERO )
265     $            NBNEXT = 2
266            END IF
267            CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
268     $                   LDZ, HERE+1, 1, NBNEXT, WORK, LWORK, INFO )
269            IF( INFO.NE.0 ) THEN
270               ILST = HERE
271               RETURN
272            END IF
273            IF( NBNEXT.EQ.1 ) THEN
274*
275*              Swap two 1-by-1 blocks.
276*
277               CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
278     $                      LDZ, HERE, 1, 1, WORK, LWORK, INFO )
279               IF( INFO.NE.0 ) THEN
280                  ILST = HERE
281                  RETURN
282               END IF
283               HERE = HERE + 1
284*
285            ELSE
286*
287*              Recompute NBNEXT in case of 2-by-2 split.
288*
289               IF( A( HERE+2, HERE+1 ).EQ.ZERO )
290     $            NBNEXT = 1
291               IF( NBNEXT.EQ.2 ) THEN
292*
293*                 2-by-2 block did not split.
294*
295                  CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ,
296     $                         Z, LDZ, HERE, 1, NBNEXT, WORK, LWORK,
297     $                         INFO )
298                  IF( INFO.NE.0 ) THEN
299                     ILST = HERE
300                     RETURN
301                  END IF
302                  HERE = HERE + 2
303               ELSE
304*
305*                 2-by-2 block did split.
306*
307                  CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ,
308     $                         Z, LDZ, HERE, 1, 1, WORK, LWORK, INFO )
309                  IF( INFO.NE.0 ) THEN
310                     ILST = HERE
311                     RETURN
312                  END IF
313                  HERE = HERE + 1
314                  CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ,
315     $                         Z, LDZ, HERE, 1, 1, WORK, LWORK, INFO )
316                  IF( INFO.NE.0 ) THEN
317                     ILST = HERE
318                     RETURN
319                  END IF
320                  HERE = HERE + 1
321               END IF
322*
323            END IF
324         END IF
325         IF( HERE.LT.ILST )
326     $      GO TO 10
327      ELSE
328         HERE = IFST
329*
330   20    CONTINUE
331*
332*        Swap with next one below.
333*
334         IF( NBF.EQ.1 .OR. NBF.EQ.2 ) THEN
335*
336*           Current block either 1-by-1 or 2-by-2.
337*
338            NBNEXT = 1
339            IF( HERE.GE.3 ) THEN
340               IF( A( HERE-1, HERE-2 ).NE.ZERO )
341     $            NBNEXT = 2
342            END IF
343            CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
344     $                   LDZ, HERE-NBNEXT, NBNEXT, NBF, WORK, LWORK,
345     $                   INFO )
346            IF( INFO.NE.0 ) THEN
347               ILST = HERE
348               RETURN
349            END IF
350            HERE = HERE - NBNEXT
351*
352*           Test if 2-by-2 block breaks into two 1-by-1 blocks.
353*
354            IF( NBF.EQ.2 ) THEN
355               IF( A( HERE+1, HERE ).EQ.ZERO )
356     $            NBF = 3
357            END IF
358*
359         ELSE
360*
361*           Current block consists of two 1-by-1 blocks, each of which
362*           must be swapped individually.
363*
364            NBNEXT = 1
365            IF( HERE.GE.3 ) THEN
366               IF( A( HERE-1, HERE-2 ).NE.ZERO )
367     $            NBNEXT = 2
368            END IF
369            CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
370     $                   LDZ, HERE-NBNEXT, NBNEXT, 1, WORK, LWORK,
371     $                   INFO )
372            IF( INFO.NE.0 ) THEN
373               ILST = HERE
374               RETURN
375            END IF
376            IF( NBNEXT.EQ.1 ) THEN
377*
378*              Swap two 1-by-1 blocks.
379*
380               CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
381     $                      LDZ, HERE, NBNEXT, 1, WORK, LWORK, INFO )
382               IF( INFO.NE.0 ) THEN
383                  ILST = HERE
384                  RETURN
385               END IF
386               HERE = HERE - 1
387            ELSE
388*
389*             Recompute NBNEXT in case of 2-by-2 split.
390*
391               IF( A( HERE, HERE-1 ).EQ.ZERO )
392     $            NBNEXT = 1
393               IF( NBNEXT.EQ.2 ) THEN
394*
395*                 2-by-2 block did not split.
396*
397                  CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ,
398     $                         Z, LDZ, HERE-1, 2, 1, WORK, LWORK, INFO )
399                  IF( INFO.NE.0 ) THEN
400                     ILST = HERE
401                     RETURN
402                  END IF
403                  HERE = HERE - 2
404               ELSE
405*
406*                 2-by-2 block did split.
407*
408                  CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ,
409     $                         Z, LDZ, HERE, 1, 1, WORK, LWORK, INFO )
410                  IF( INFO.NE.0 ) THEN
411                     ILST = HERE
412                     RETURN
413                  END IF
414                  HERE = HERE - 1
415                  CALL DTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ,
416     $                         Z, LDZ, HERE, 1, 1, WORK, LWORK, INFO )
417                  IF( INFO.NE.0 ) THEN
418                     ILST = HERE
419                     RETURN
420                  END IF
421                  HERE = HERE - 1
422               END IF
423            END IF
424         END IF
425         IF( HERE.GT.ILST )
426     $      GO TO 20
427      END IF
428      ILST = HERE
429      WORK( 1 ) = LWMIN
430      RETURN
431*
432*     End of DTGEXC
433*
434      END
435