ztrsyl man page on OpenIndiana

Man page or keyword search:  
man Server   20441 pages
apropos Keyword Search (all sections)
Output format
OpenIndiana logo
[printable version]

ztrsyl(3P)		    Sun Performance Library		    ztrsyl(3P)

NAME
       ztrsyl - solve the complex Sylvester matrix equation

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

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

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

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

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

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

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

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

   C INTERFACE
       #include <sunperf.h>

       void  ztrsyl(char trana, char tranb, int isgn, int m, int n, doublecom‐
		 plex *a, int lda, doublecomplex *b,  int  ldb,	 doublecomplex
		 *c, int ldc, double *scale, int *info);

       void  ztrsyl_64(char trana, char tranb, long isgn, long m, long n, dou‐
		 blecomplex *a, long lda, doublecomplex *b, long ldb,  double‐
		 complex *c, long ldc, double *scale, long *info);

PURPOSE
       ztrsyl solves the complex 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**H, and A and B are both upper 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.

ARGUMENTS
       TRANA (input)
		 Specifies the option op(A):
		 = 'N': op(A) = A    (No transpose)
		 = 'C': op(A) = A**H (Conjugate transpose)

       TRANB (input)
		 Specifies the option op(B):
		 = 'N': op(B) = B    (No transpose)
		 = 'C': op(B) = B**H (Conjugate transpose)

       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 triangular matrix A.

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

       B (input) The upper triangular matrix B.

       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 overflow in X.

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

				  6 Mar 2009			    ztrsyl(3P)
[top]

List of man pages available for OpenIndiana

Copyright (c) for man pages and the logo by the respective OS vendor.

For those who want to learn more, the polarhome community provides shell access and support.

[legal] [privacy] [GNU] [policy] [cookies] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.
Based on Fawad Halim's script.
....................................................................
Vote for polarhome
Free Shell Accounts :: the biggest list on the net