Contents


NAME

     strsyl - solve the real Sylvester matrix equation

SYNOPSIS

     SUBROUTINE STRSYL(TRANA, TRANB, ISGN, M, N, A, LDA, B, LDB, C, LDC,
           SCALE, INFO)

     CHARACTER * 1 TRANA, TRANB
     INTEGER ISGN, M, N, LDA, LDB, LDC, INFO
     REAL SCALE
     REAL A(LDA,*), B(LDB,*), C(LDC,*)

     SUBROUTINE STRSYL_64(TRANA, TRANB, ISGN, M, N, A, LDA, B, LDB, C,
           LDC, SCALE, INFO)

     CHARACTER * 1 TRANA, TRANB
     INTEGER*8 ISGN, M, N, LDA, LDB, LDC, INFO
     REAL SCALE
     REAL A(LDA,*), B(LDB,*), C(LDC,*)

  F95 INTERFACE
     SUBROUTINE TRSYL(TRANA, TRANB, ISGN, M, N, A, [LDA], B, [LDB], C,
            [LDC], SCALE, [INFO])

     CHARACTER(LEN=1) :: TRANA, TRANB
     INTEGER :: ISGN, M, N, LDA, LDB, LDC, INFO
     REAL :: SCALE
     REAL, DIMENSION(:,:) :: A, B, C

     SUBROUTINE TRSYL_64(TRANA, TRANB, ISGN, M, N, A, [LDA], B, [LDB], C,
            [LDC], SCALE, [INFO])

     CHARACTER(LEN=1) :: TRANA, TRANB
     INTEGER(8) :: ISGN, M, N, LDA, LDB, LDC, INFO
     REAL :: SCALE
     REAL, DIMENSION(:,:) :: A, B, C

  C INTERFACE
     #include <sunperf.h>

     void strsyl(char trana, char tranb, int isgn, int m, int  n,
               float  *a,  int  lda, float *b, int ldb, float *c,
               int ldc, float *scale, int *info);

     void strsyl_64(char trana, char tranb, long  isgn,  long  m,
               long  n,  float  *a, long lda, float *b, long ldb,
               float *c, long ldc, float *scale, long *info);

PURPOSE

     strsyl solves the real Sylvester matrix equation:

        op(A)*X + X*op(B) = scale*C or
        op(A)*X - X*op(B) = scale*C,

     where op(A) = A or A**T, and  A and B are both upper  quasi-
     triangular. A is M-by-M and B is N-by-N; the right hand side
     C and the solution X are M-by-N;  and  scale  is  an  output
     scale factor, set <= 1 to avoid overflow in X.

     A and B must be in Schur  canonical  form  (as  returned  by
     SHSEQR),  that is, block upper triangular with 1-by-1 and 2-
     by-2 diagonal blocks; each 2-by-2  diagonal  block  has  its
     diagonal  elements  equal  and  its off-diagonal elements of
     opposite sign.

ARGUMENTS

     TRANA (input)
               Specifies the option op(A):
               = 'N': op(A) = A    (No transpose)
               = 'T': op(A) = A**T (Transpose)
               = 'C': op(A) = A**H (Conjugate transpose  =  Tran-
               spose)

     TRANB (input)
               Specifies the option op(B):
               = 'N': op(B) = B    (No transpose)
               = 'T': op(B) = B**T (Transpose)
               = 'C': op(B) = B**H (Conjugate transpose  =  Tran-
               spose)

     ISGN (input)
               Specifies the sign in the equation:
               = +1: solve op(A)*X + X*op(B) = scale*C
               = -1: solve op(A)*X - X*op(B) = scale*C

     M (input) The order of the matrix A, and the number of  rows
               in the matrices X and C. M >= 0.

     N (input) The order of the  matrix  B,  and  the  number  of
               columns in the matrices X and C. N >= 0.

     A (input) The upper  quasi-triangular  matrix  A,  in  Schur
               canonical form.
     LDA (input)
               The leading dimension  of  the  array  A.  LDA  >=
               max(1,M).

     B (input) The upper  quasi-triangular  matrix  B,  in  Schur
               canonical form.

     LDB (input)
               The leading dimension  of  the  array  B.  LDB  >=
               max(1,N).

     C (input/output)
               On entry, the M-by-N right hand side matrix C.  On
               exit, C is overwritten by the solution matrix X.

     LDC (input)
               The leading dimension  of  the  array  C.  LDC  >=
               max(1,M)

     SCALE (output)
               The scale factor, scale, set <= 1 to  avoid  over-
               flow in X.

     INFO (output)
               = 0: successful exit
               < 0: if INFO = -i, the i-th argument had an  ille-
               gal value
               = 1: A and B have  common  or  very  close  eigen-
               values;  perturbed  values  were used to solve the
               equation (but the matrices A and B are unchanged).