*nix Documentation Project
·  Home
 +   man pages
·  Linux HOWTOs
·  FreeBSD Tips
·  *niX Forums

  man pages->IRIX man pages -> complib/slasr (3)              
Title
Content
Arch
Section
 

Contents


SLASR(3F)							     SLASR(3F)


NAME    [Toc]    [Back]

     SLASR - perform the transformation	  A := P*A, when SIDE =	'L' or 'l' (
     Left-hand side )	A := A*P', when	SIDE = 'R' or 'r' ( Right-hand side )
     where A is	an m by	n real matrix and P is an orthogonal matrix,

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	SLASR( SIDE, PIVOT, DIRECT, M, N, C, S,	A, LDA )

	 CHARACTER     DIRECT, PIVOT, SIDE

	 INTEGER       LDA, M, N

	 REAL	       A( LDA, * ), C( * ), S( * )

PURPOSE    [Toc]    [Back]

     SLASR   performs the transformation consisting of a sequence of plane
     rotations determined by the parameters PIVOT and DIRECT as	follows	( z =
     m when SIDE = 'L' or 'l' and z = n	when SIDE = 'R'	or 'r' ):

     When  DIRECT = 'F'	or 'f'	( Forward sequence ) then

	P = P( z - 1 )*...*P( 2	)*P( 1 ),

     and when DIRECT = 'B' or 'b'  ( Backward sequence ) then

	P = P( 1 )*P( 2	)*...*P( z - 1 ),

     where  P( k ) is a	plane rotation matrix for the following	planes:

	when  PIVOT = 'V' or 'v'  ( Variable pivot ),
	   the plane ( k, k + 1	)

	when  PIVOT = 'T' or 't'  ( Top	pivot ),
	   the plane ( 1, k + 1	)

	when  PIVOT = 'B' or 'b'  ( Bottom pivot ),
	   the plane ( k, z )

     c(	k ) and	s( k )	must contain the  cosine and sine that define the
     matrix  P(	k ).  The two by two plane rotation part of the	matrix P( k ),
     R(	k ), is	assumed	to be of the form

	R( k ) = (  c( k )  s( k ) ).
		 ( -s( k )  c( k ) )

     This version vectorises across rows of the	array A	when SIDE = 'L'.

ARGUMENTS    [Toc]    [Back]

     SIDE    (input) CHARACTER*1
	     Specifies whether the plane rotation matrix P is applied to A on
	     the left or the right.  = 'L':  Left, compute A :=	P*A



									Page 1






SLASR(3F)							     SLASR(3F)



	     = 'R':  Right, compute A:=	A*P'

     DIRECT  (input) CHARACTER*1
	     Specifies whether P is a forward or backward sequence of plane
	     rotations.	 = 'F':	 Forward, P = P( z - 1 )*...*P(	2 )*P( 1 )
	     = 'B':  Backward, P = P( 1	)*P( 2 )*...*P(	z - 1 )

     PIVOT   (input) CHARACTER*1
	     Specifies the plane for which P(k)	is a plane rotation matrix.  =
	     'V':  Variable pivot, the plane (k,k+1)
	     = 'T':  Top pivot,	the plane (1,k+1)
	     = 'B':  Bottom pivot, the plane (k,z)

     M	     (input) INTEGER
	     The number	of rows	of the matrix A.  If m <= 1, an	immediate
	     return is effected.

     N	     (input) INTEGER
	     The number	of columns of the matrix A.  If	n <= 1,	an immediate
	     return is effected.

	     C,	S    (input) REAL arrays, dimension (M-1) if SIDE = 'L'	(N-1)
	     if	SIDE = 'R' c(k)	and s(k) contain the cosine and	sine that
	     define the	matrix P(k).  The two by two plane rotation part of
	     the matrix	P(k), R(k), is assumed to be of	the form R( k )	= (
	     c(	k )  s(	k ) ).	( -s( k	)  c( k	) )

     A	     (input/output) REAL array,	dimension (LDA,N)
	     The m by n	matrix A.  On exit, A is overwritten by	P*A if SIDE =
	     'R' or by A*P' if SIDE = 'L'.

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


NAME    [Toc]    [Back]

     SLASR - perform the transformation	  A := P*A, when SIDE =	'L' or 'l' (
     Left-hand side )	A := A*P', when	SIDE = 'R' or 'r' ( Right-hand side )
     where A is	an m by	n real matrix and P is an orthogonal matrix,

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	SLASR( SIDE, PIVOT, DIRECT, M, N, C, S,	A, LDA )

	 CHARACTER     DIRECT, PIVOT, SIDE

	 INTEGER       LDA, M, N

	 REAL	       A( LDA, * ), C( * ), S( * )

PURPOSE    [Toc]    [Back]

     SLASR   performs the transformation consisting of a sequence of plane
     rotations determined by the parameters PIVOT and DIRECT as	follows	( z =
     m when SIDE = 'L' or 'l' and z = n	when SIDE = 'R'	or 'r' ):

     When  DIRECT = 'F'	or 'f'	( Forward sequence ) then

	P = P( z - 1 )*...*P( 2	)*P( 1 ),

     and when DIRECT = 'B' or 'b'  ( Backward sequence ) then

	P = P( 1 )*P( 2	)*...*P( z - 1 ),

     where  P( k ) is a	plane rotation matrix for the following	planes:

	when  PIVOT = 'V' or 'v'  ( Variable pivot ),
	   the plane ( k, k + 1	)

	when  PIVOT = 'T' or 't'  ( Top	pivot ),
	   the plane ( 1, k + 1	)

	when  PIVOT = 'B' or 'b'  ( Bottom pivot ),
	   the plane ( k, z )

     c(	k ) and	s( k )	must contain the  cosine and sine that define the
     matrix  P(	k ).  The two by two plane rotation part of the	matrix P( k ),
     R(	k ), is	assumed	to be of the form

	R( k ) = (  c( k )  s( k ) ).
		 ( -s( k )  c( k ) )

     This version vectorises across rows of the	array A	when SIDE = 'L'.

ARGUMENTS    [Toc]    [Back]

     SIDE    (input) CHARACTER*1
	     Specifies whether the plane rotation matrix P is applied to A on
	     the left or the right.  = 'L':  Left, compute A :=	P*A



									Page 1






SLASR(3F)							     SLASR(3F)



	     = 'R':  Right, compute A:=	A*P'

     DIRECT  (input) CHARACTER*1
	     Specifies whether P is a forward or backward sequence of plane
	     rotations.	 = 'F':	 Forward, P = P( z - 1 )*...*P(	2 )*P( 1 )
	     = 'B':  Backward, P = P( 1	)*P( 2 )*...*P(	z - 1 )

     PIVOT   (input) CHARACTER*1
	     Specifies the plane for which P(k)	is a plane rotation matrix.  =
	     'V':  Variable pivot, the plane (k,k+1)
	     = 'T':  Top pivot,	the plane (1,k+1)
	     = 'B':  Bottom pivot, the plane (k,z)

     M	     (input) INTEGER
	     The number	of rows	of the matrix A.  If m <= 1, an	immediate
	     return is effected.

     N	     (input) INTEGER
	     The number	of columns of the matrix A.  If	n <= 1,	an immediate
	     return is effected.

	     C,	S    (input) REAL arrays, dimension (M-1) if SIDE = 'L'	(N-1)
	     if	SIDE = 'R' c(k)	and s(k) contain the cosine and	sine that
	     define the	matrix P(k).  The two by two plane rotation part of
	     the matrix	P(k), R(k), is assumed to be of	the form R( k )	= (
	     c(	k )  s(	k ) ).	( -s( k	)  c( k	) )

     A	     (input/output) REAL array,	dimension (LDA,N)
	     The m by n	matrix A.  On exit, A is overwritten by	P*A if SIDE =
	     'R' or by A*P' if SIDE = 'L'.

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


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
sorgbr IRIX generate one of the real orthogonal matrices Q or P**T determined by SGEBRD when reducing a real matrix A to b
dorgbr IRIX generate one of the real orthogonal matrices Q or P**T determined by DGEBRD when reducing a real matrix A to b
ssytrd IRIX reduce a real symmetric matrix A to real symmetric tridiagonal form T by an orthogonal similarity transformati
dsytrd IRIX reduce a real symmetric matrix A to real symmetric tridiagonal form T by an orthogonal similarity transformati
SSVDC IRIX SSVDC is a subroutine to reduce a real NxP matrix X by orthogonal transformations U and V to diagonal form. Th
sgehd2 IRIX reduce a real general matrix A to upper Hessenberg form H by an orthogonal similarity transformation
dgebrd IRIX reduce a general real M-by-N matrix A to upper or lower bidiagonal form B by an orthogonal transformation
dgebd2 IRIX reduce a real general m by n matrix A to upper or lower bidiagonal form B by an orthogonal transformation
sgehrd IRIX reduce a real general matrix A to upper Hessenberg form H by an orthogonal similarity transformation
sgebrd IRIX reduce a general real M-by-N matrix A to upper or lower bidiagonal form B by an orthogonal transformation
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service