SLAQTR man page on IRIX

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



SLAQTR(3F)							    SLAQTR(3F)

NAME
     SLAQTR - solve the real quasi-triangular system   op(T)*p = scale*c, if
     LREAL = .TRUE

SYNOPSIS
     SUBROUTINE SLAQTR( LTRAN, LREAL, N, T, LDT, B, W, SCALE, X, WORK, INFO )

	 LOGICAL	LREAL, LTRAN

	 INTEGER	INFO, LDT, N

	 REAL		SCALE, W

	 REAL		B( * ), T( LDT, * ), WORK( * ), X( * )

PURPOSE
     SLAQTR solves the real quasi-triangular system

     or the complex quasi-triangular systems

		op(T + iB)*(p+iq) = scale*(c+id),  if LREAL = .FALSE.

     in real arithmetic, where T is upper quasi-triangular.
     If LREAL = .FALSE., then the first diagonal block of T must be 1 by 1, B
     is the specially structured matrix

		    B = [ b(1) b(2) ... b(n) ]
			[	w	     ]
			[	    w	     ]
			[	       .     ]
			[		  w  ]

     op(A) = A or A', A' denotes the conjugate transpose of
     matrix A.

     On input, X = [ c ].  On output, X = [ p ].
		   [ d ]		  [ q ]

     This subroutine is designed for the condition number estimation in
     routine STRSNA.

ARGUMENTS
     LTRAN   (input) LOGICAL
	     On entry, LTRAN specifies the option of conjugate transpose:  =
	     .FALSE.,	 op(T+i*B) = T+i*B, = .TRUE.,	  op(T+i*B) =
	     (T+i*B)'.

     LREAL   (input) LOGICAL
	     On entry, LREAL specifies the input matrix structure:  = .FALSE.,
	     the input is complex = .TRUE.,	the input is real

									Page 1

SLAQTR(3F)							    SLAQTR(3F)

     N	     (input) INTEGER
	     On entry, N specifies the order of T+i*B. N >= 0.

     T	     (input) REAL array, dimension (LDT,N)
	     On entry, T contains a matrix in Schur canonical form.  If LREAL
	     = .FALSE., then the first diagonal block of T must be 1 by 1.

     LDT     (input) INTEGER
	     The leading dimension of the matrix T. LDT >= max(1,N).

     B	     (input) REAL array, dimension (N)
	     On entry, B contains the elements to form the matrix B as
	     described above.  If LREAL = .TRUE., B is not referenced.

     W	     (input) REAL
	     On entry, W is the diagonal element of the matrix B.  If LREAL =
	     .TRUE., W is not referenced.

     SCALE   (output) REAL
	     On exit, SCALE is the scale factor.

     X	     (input/output) REAL array, dimension (2*N)
	     On entry, X contains the right hand side of the system.  On exit,
	     X is overwritten by the solution.

     WORK    (workspace) REAL array, dimension (N)

     INFO    (output) INTEGER
	     On exit, INFO is set to 0: successful exit.
	     1: the some diagonal 1 by 1 block has been perturbed by a small
	     number SMIN to keep nonsingularity.  2: the some diagonal 2 by 2
	     block has been perturbed by a small number in SLALN2 to keep
	     nonsingularity.  NOTE: In the interests of speed, this routine
	     does not check the inputs for errors.

									Page 2

[top]

List of man pages available for IRIX

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