tgsyl Interface

public interface tgsyl

TGSYL solves the generalized Sylvester equation: 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 complex entries. A, B, D and E are upper triangular (i.e., (A,D) and (B,E) in generalized Schur form). 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 = scaleb, where Z is defined as Z = [ kron(In, A) -kron(BH, Im) ] (2) [ kron(In, D) -kron(EH, Im) ], Here Ix is the identity matrix of size x and XH is the conjugate transpose of X. Kron(X, Y) is the Kronecker product between the matrices X and Y. If TRANS = 'C', y in the conjugate transposed system ZH y = scaleb is solved for, which is equivalent to solve for R and L in AH * R + DH * L = scale * C (3) R * BH + L * E*H = scale * -F This case (TRANS = 'C') 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 CLACON. If IJOB >= 1, TGSYL 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. This is a level-3 BLAS algorithm.


Subroutines

public pure subroutine ctgsyl(trans, ijob, m, n, a, lda, b, ldb, c, ldc, d, ldd, e, lde, f, ldf, scale, dif, work, lwork, iwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: ijob
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
complex(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=sp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
complex(kind=sp), intent(inout) :: c(ldc,*)
integer(kind=ilp), intent(in) :: ldc
complex(kind=sp), intent(in) :: d(ldd,*)
integer(kind=ilp), intent(in) :: ldd
complex(kind=sp), intent(in) :: e(lde,*)
integer(kind=ilp), intent(in) :: lde
complex(kind=sp), intent(inout) :: f(ldf,*)
integer(kind=ilp), intent(in) :: ldf
real(kind=sp), intent(out) :: scale
real(kind=sp), intent(out) :: dif
complex(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: iwork(*)
integer(kind=ilp), intent(out) :: info

public pure subroutine dtgsyl(trans, ijob, m, n, a, lda, b, ldb, c, ldc, d, ldd, e, lde, f, ldf, scale, dif, work, lwork, iwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: ijob
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
real(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=dp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=dp), intent(inout) :: c(ldc,*)
integer(kind=ilp), intent(in) :: ldc
real(kind=dp), intent(in) :: d(ldd,*)
integer(kind=ilp), intent(in) :: ldd
real(kind=dp), intent(in) :: e(lde,*)
integer(kind=ilp), intent(in) :: lde
real(kind=dp), intent(inout) :: f(ldf,*)
integer(kind=ilp), intent(in) :: ldf
real(kind=dp), intent(out) :: scale
real(kind=dp), intent(out) :: dif
real(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: iwork(*)
integer(kind=ilp), intent(out) :: info

public pure subroutine stgsyl(trans, ijob, m, n, a, lda, b, ldb, c, ldc, d, ldd, e, lde, f, ldf, scale, dif, work, lwork, iwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: ijob
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
real(kind=sp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
real(kind=sp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
real(kind=sp), intent(inout) :: c(ldc,*)
integer(kind=ilp), intent(in) :: ldc
real(kind=sp), intent(in) :: d(ldd,*)
integer(kind=ilp), intent(in) :: ldd
real(kind=sp), intent(in) :: e(lde,*)
integer(kind=ilp), intent(in) :: lde
real(kind=sp), intent(inout) :: f(ldf,*)
integer(kind=ilp), intent(in) :: ldf
real(kind=sp), intent(out) :: scale
real(kind=sp), intent(out) :: dif
real(kind=sp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: iwork(*)
integer(kind=ilp), intent(out) :: info

public pure subroutine ztgsyl(trans, ijob, m, n, a, lda, b, ldb, c, ldc, d, ldd, e, lde, f, ldf, scale, dif, work, lwork, iwork, info)

Arguments

Type IntentOptional Attributes Name
character(len=1), intent(in) :: trans
integer(kind=ilp), intent(in) :: ijob
integer(kind=ilp), intent(in) :: m
integer(kind=ilp), intent(in) :: n
complex(kind=dp), intent(in) :: a(lda,*)
integer(kind=ilp), intent(in) :: lda
complex(kind=dp), intent(in) :: b(ldb,*)
integer(kind=ilp), intent(in) :: ldb
complex(kind=dp), intent(inout) :: c(ldc,*)
integer(kind=ilp), intent(in) :: ldc
complex(kind=dp), intent(in) :: d(ldd,*)
integer(kind=ilp), intent(in) :: ldd
complex(kind=dp), intent(in) :: e(lde,*)
integer(kind=ilp), intent(in) :: lde
complex(kind=dp), intent(inout) :: f(ldf,*)
integer(kind=ilp), intent(in) :: ldf
real(kind=dp), intent(out) :: scale
real(kind=dp), intent(out) :: dif
complex(kind=dp), intent(out) :: work(*)
integer(kind=ilp), intent(in) :: lwork
integer(kind=ilp), intent(out) :: iwork(*)
integer(kind=ilp), intent(out) :: info

Module Procedures

public interface stdlib_ctgsyl()

Arguments

None

public interface stdlib_dtgsyl()

Arguments

None

public interface stdlib_stgsyl()

Arguments

None

public interface stdlib_ztgsyl()

Arguments

None