SUBROUTINE STGSYL( TRANS, IJOB, M, N, A, LDA, B, LDB, C, LDC, D, * LDD, E, LDE, F, LDF, SCALE, DIF, WORK, LWORK, IWORK, INFO) CHARACTER * 1 TRANS INTEGER IJOB, M, N, LDA, LDB, LDC, LDD, LDE, LDF, LWORK, INFO INTEGER IWORK(*) REAL SCALE, DIF REAL A(LDA,*), B(LDB,*), C(LDC,*), D(LDD,*), E(LDE,*), F(LDF,*), WORK(*) SUBROUTINE STGSYL_64( TRANS, IJOB, M, N, A, LDA, B, LDB, C, LDC, D, * LDD, E, LDE, F, LDF, SCALE, DIF, WORK, LWORK, IWORK, INFO) CHARACTER * 1 TRANS INTEGER*8 IJOB, M, N, LDA, LDB, LDC, LDD, LDE, LDF, LWORK, INFO INTEGER*8 IWORK(*) REAL SCALE, DIF REAL A(LDA,*), B(LDB,*), C(LDC,*), D(LDD,*), E(LDE,*), F(LDF,*), WORK(*)
SUBROUTINE TGSYL( TRANS, IJOB, [M], [N], A, [LDA], B, [LDB], C, [LDC], * D, [LDD], E, [LDE], F, [LDF], SCALE, DIF, [WORK], [LWORK], [IWORK], * [INFO]) CHARACTER(LEN=1) :: TRANS INTEGER :: IJOB, M, N, LDA, LDB, LDC, LDD, LDE, LDF, LWORK, INFO INTEGER, DIMENSION(:) :: IWORK REAL :: SCALE, DIF REAL, DIMENSION(:) :: WORK REAL, DIMENSION(:,:) :: A, B, C, D, E, F SUBROUTINE TGSYL_64( TRANS, IJOB, [M], [N], A, [LDA], B, [LDB], C, * [LDC], D, [LDD], E, [LDE], F, [LDF], SCALE, DIF, [WORK], [LWORK], * [IWORK], [INFO]) CHARACTER(LEN=1) :: TRANS INTEGER(8) :: IJOB, M, N, LDA, LDB, LDC, LDD, LDE, LDF, LWORK, INFO INTEGER(8), DIMENSION(:) :: IWORK REAL :: SCALE, DIF REAL, DIMENSION(:) :: WORK REAL, DIMENSION(:,:) :: A, B, C, D, E, F
void stgsyl(char trans, int ijob, int m, int n, float *a, int lda, float *b, int ldb, float *c, int ldc, float *d, int ldd, float *e, int lde, float *f, int ldf, float *scale, float *dif, int *info);
void stgsyl_64(char trans, long ijob, long m, long n, float *a, long lda, float *b, long ldb, float *c, long ldc, float *d, long ldd, float *e, long lde, float *f, long ldf, float *scale, float *dif, long *info);
A * R - L * B = scale * C (1)
D * R - L * E = scale * F
where R and L are unknown m-by-n matrices, (A, D), (B, E) and (C, F) are given matrix pairs of size m-by-m, n-by-n and m-by-n, respectively, with real entries. (A, D) and (B, E) must be in generalized (real) Schur canonical form, i.e. A, B are upper quasi triangular and D, E are upper triangular.
The solution (R, L) overwrites (C, F). 0 <= SCALE <= 1 is an output scaling factor chosen to avoid overflow.
In matrix notation (1) is equivalent to solve Zx = scale b, where Z is defined as
Z = [ kron(In, A) -kron(B', Im) ] (2)
[ kron(In, D) -kron(E', Im) ].
Here Ik is the identity matrix of size k and X' is the transpose of X. kron(X, Y) is the Kronecker product between the matrices X and Y.
If TRANS = 'T', STGSYL solves the transposed system Z'*y = scale*b, which is equivalent to solve for R and L in
A' * R + D' * L = scale * C (3)
R * B' + L * E' = scale * (-F)
This case (TRANS = 'T') is used to compute an one-norm-based estimate of Dif[(A,D), (B,E)], the separation between the matrix pairs (A,D) and (B,E), using SLACON.
If IJOB >= 1, STGSYL computes a Frobenius norm-based estimate of Dif[(A,D),(B,E)]. That is, the reciprocal of a lower bound on the reciprocal of the smallest singular value of Z. See [1-2] for more information.
This is a level 3 BLAS algorithm.
If LWORK = -1, then a workspace query is assumed; the routine only calculates the optimal size of the WORK array, returns this value as the first entry of the WORK array, and no error message related to LWORK is issued by XERBLA.