1STGSY2(1)           LAPACK auxiliary routine (version 3.2)           STGSY2(1)
2
3
4

NAME

6       STGSY2 - solves the generalized Sylvester equation
7

SYNOPSIS

9       SUBROUTINE STGSY2( TRANS,  IJOB,  M, N, A, LDA, B, LDB, C, LDC, D, LDD,
10                          E, LDE, F, LDF, SCALE,  RDSUM,  RDSCAL,  IWORK,  PQ,
11                          INFO )
12
13           CHARACTER      TRANS
14
15           INTEGER        IJOB, INFO, LDA, LDB, LDC, LDD, LDE, LDF, M, N, PQ
16
17           REAL           RDSCAL, RDSUM, SCALE
18
19           INTEGER        IWORK( * )
20
21           REAL           A(  LDA, * ), B( LDB, * ), C( LDC, * ), D( LDD, * ),
22                          E( LDE, * ), F( LDF, * )
23

PURPOSE

25       STGSY2 solves the generalized Sylvester equation:
26                   A * R - L * B = scale * C                (1)
27                   D * R - L * E = scale * F,
28       using Level 1 and 2 BLAS. where R and L are  unknown  M-by-N  matrices,
29       (A, D), (B, E) and (C, F) are given matrix pairs of size M-by-M, N-by-N
30       and M-by-N, respectively, with real entries. (A, D) and (B, E) must  be
31       in generalized Schur canonical form, i.e. A, B are upper quasi triangu‐
32       lar and D, E are upper triangular. The solution (R, L)  overwrites  (C,
33       F).  0  <= SCALE <= 1 is an output scaling factor chosen to avoid over‐
34       flow.
35       In matrix notation solving equation (1)  corresponds  to  solve  Z*x  =
36       scale*b, where Z is defined as
37              Z = [ kron(In, A)  -kron(B', Im) ]             (2)
38                  [ kron(In, D)  -kron(E', Im) ],
39       Ik  is  the  identity  matrix  of  size k and X' is the transpose of X.
40       kron(X, Y) is the Kronecker product between the matrices X and  Y.   In
41       the  process  of  solving  (1), we solve a number of such systems where
42       Dim(In), Dim(In) = 1 or 2.
43       If TRANS = 'T', solve the transposed system Z'*y = scale*b for y, which
44       is equivalent to solve for R and L in
45                   A' * R  + D' * L   = scale *  C           (3)
46                   R  * B' + L  * E'  = scale * -F
47       This  case  is  used  to  compute  an estimate of Dif[(A, D), (B, E)] =
48       sigma_min(Z) using reverse communicaton with SLACON.
49       STGSY2 also (IJOB >= 1) contributes to the computation in STGSYL of  an
50       upper  bound  on the separation between to matrix pairs. Then the input
51       (A, D), (B, E) are sub-pencils of the matrix pair in STGSYL. See STGSYL
52       for details.
53

ARGUMENTS

55       TRANS   (input) CHARACTER*1
56               =  'N',  solve  the generalized Sylvester equation (1).  = 'T':
57               solve the 'transposed' system (3).
58
59       IJOB    (input) INTEGER
60               Specifies what kind of functionality to  be  performed.   =  0:
61               solve (1) only.
62               =  1:  A  contribution from this subsystem to a Frobenius norm-
63               based estimate of the separation between two  matrix  pairs  is
64               computed.  (look  ahead strategy is used).  = 2: A contribution
65               from this subsystem to a Frobenius norm-based estimate  of  the
66               separation  between  two  matrix  pairs is computed. (SGECON on
67               sub-systems is used.)  Not referenced if TRANS = 'T'.
68
69       M       (input) INTEGER
70               On entry, M specifies the order of A and D, and the row  dimen‐
71               sion of C, F, R and L.
72
73       N       (input) INTEGER
74               On  entry,  N  specifies  the  order of B and E, and the column
75               dimension of C, F, R and L.
76
77       A       (input) REAL array, dimension (LDA, M)
78               On entry, A contains an upper quasi triangular matrix.
79
80       LDA     (input) INTEGER
81               The leading dimension of the matrix A. LDA >= max(1, M).
82
83       B       (input) REAL array, dimension (LDB, N)
84               On entry, B contains an upper quasi triangular matrix.
85
86       LDB     (input) INTEGER
87               The leading dimension of the matrix B. LDB >= max(1, N).
88
89       C       (input/output) REAL array, dimension (LDC, N)
90               On entry, C contains the right-hand-side of  the  first  matrix
91               equation  in (1).  On exit, if IJOB = 0, C has been overwritten
92               by the solution R.
93
94       LDC     (input) INTEGER
95               The leading dimension of the matrix C. LDC >= max(1, M).
96
97       D       (input) REAL array, dimension (LDD, M)
98               On entry, D contains an upper triangular matrix.
99
100       LDD     (input) INTEGER
101               The leading dimension of the matrix D. LDD >= max(1, M).
102
103       E       (input) REAL array, dimension (LDE, N)
104               On entry, E contains an upper triangular matrix.
105
106       LDE     (input) INTEGER
107               The leading dimension of the matrix E. LDE >= max(1, N).
108
109       F       (input/output) REAL array, dimension (LDF, N)
110               On entry, F contains the right-hand-side of the  second  matrix
111               equation  in (1).  On exit, if IJOB = 0, F has been overwritten
112               by the solution L.
113
114       LDF     (input) INTEGER
115               The leading dimension of the matrix F. LDF >= max(1, M).
116
117       SCALE   (output) REAL
118               On exit, 0 <= SCALE <= 1. If 0 < SCALE < 1, the solutions R and
119               L (C and F on entry) will hold the solutions to a slightly per‐
120               turbed system but the input matrices A, B, D  and  E  have  not
121               been  changed. If SCALE = 0, R and L will hold the solutions to
122               the homogeneous system with C = F = 0. Normally, SCALE = 1.
123
124       RDSUM   (input/output) REAL
125               On entry, the sum of squares of computed contributions  to  the
126               Dif-estimate  under  computation  by  STGSYL, where the scaling
127               factor RDSCAL (see below) has been factored out.  On exit,  the
128               corresponding  sum  of  squares  updated with the contributions
129               from the current sub-system.  If  TRANS  =  'T'  RDSUM  is  not
130               touched.  NOTE: RDSUM only makes sense when STGSY2 is called by
131               STGSYL.
132
133       RDSCAL  (input/output) REAL
134               On entry, scaling factor used to prevent overflow in RDSUM.  On
135               exit,  RDSCAL  is  updated  w.r.t. the current contributions in
136               RDSUM.  If TRANS = 'T', RDSCAL is not  touched.   NOTE:  RDSCAL
137               only makes sense when STGSY2 is called by STGSYL.
138
139       IWORK   (workspace) INTEGER array, dimension (M+N+2)
140
141       PQ      (output) INTEGER
142               On  exit,  the number of subsystems (of size 2-by-2, 4-by-4 and
143               8-by-8) solved by this routine.
144
145       INFO    (output) INTEGER
146               On exit, if INFO is set to =0: Successful exit
147               <0: If INFO = -i, the i-th argument had an illegal value.
148               >0: The matrix pairs (A, D) and (B,  E)  have  common  or  very
149               close eigenvalues.
150

FURTHER DETAILS

152       Based on contributions by
153          Bo Kagstrom and Peter Poromaa, Department of Computing Science,
154          Umea University, S-901 87 Umea, Sweden.
155
156
157
158 LAPACK auxiliary routine (versionNo3v.e2m)ber 2008                       STGSY2(1)
Impressum