diff libcruft/lapack/dlasr.f @ 7034:68db500cb558

[project @ 2007-10-16 18:54:19 by jwe]
author jwe
date Tue, 16 Oct 2007 18:54:23 +0000
parents 15cddaacbc2d
children
line wrap: on
line diff
--- a/libcruft/lapack/dlasr.f	Tue Oct 16 17:46:44 2007 +0000
+++ b/libcruft/lapack/dlasr.f	Tue Oct 16 18:54:23 2007 +0000
@@ -1,9 +1,8 @@
       SUBROUTINE DLASR( SIDE, PIVOT, DIRECT, M, N, C, S, A, LDA )
 *
-*  -- LAPACK auxiliary routine (version 3.0) --
-*     Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
-*     Courant Institute, Argonne National Lab, and Rice University
-*     October 31, 1992
+*  -- LAPACK auxiliary routine (version 3.1) --
+*     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+*     November 2006
 *
 *     .. Scalar Arguments ..
       CHARACTER          DIRECT, PIVOT, SIDE
@@ -16,44 +15,77 @@
 *  Purpose
 *  =======
 *
-*  DLASR   performs 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,
-*  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'.
+*  DLASR applies a sequence of plane rotations to a real matrix A,
+*  from either the left or the right.
+*  
+*  When SIDE = 'L', the transformation takes the form
+*  
+*     A := P*A
+*  
+*  and when SIDE = 'R', the transformation takes the form
+*  
+*     A := A*P**T
+*  
+*  where P is an orthogonal matrix consisting of a sequence of z plane
+*  rotations, with z = M when SIDE = 'L' and z = N when SIDE = 'R',
+*  and P**T is the transpose of P.
+*  
+*  When DIRECT = 'F' (Forward sequence), then
+*  
+*     P = P(z-1) * ... * P(2) * P(1)
+*  
+*  and when DIRECT = 'B' (Backward sequence), then
+*  
+*     P = P(1) * P(2) * ... * P(z-1)
+*  
+*  where P(k) is a plane rotation matrix defined by the 2-by-2 rotation
+*  
+*     R(k) = (  c(k)  s(k) )
+*          = ( -s(k)  c(k) ).
+*  
+*  When PIVOT = 'V' (Variable pivot), the rotation is performed
+*  for the plane (k,k+1), i.e., P(k) has the form
+*  
+*     P(k) = (  1                                            )
+*            (       ...                                     )
+*            (              1                                )
+*            (                   c(k)  s(k)                  )
+*            (                  -s(k)  c(k)                  )
+*            (                                1              )
+*            (                                     ...       )
+*            (                                            1  )
+*  
+*  where R(k) appears as a rank-2 modification to the identity matrix in
+*  rows and columns k and k+1.
+*  
+*  When PIVOT = 'T' (Top pivot), the rotation is performed for the
+*  plane (1,k+1), so P(k) has the form
+*  
+*     P(k) = (  c(k)                    s(k)                 )
+*            (         1                                     )
+*            (              ...                              )
+*            (                     1                         )
+*            ( -s(k)                    c(k)                 )
+*            (                                 1             )
+*            (                                      ...      )
+*            (                                             1 )
+*  
+*  where R(k) appears in rows and columns 1 and k+1.
+*  
+*  Similarly, when PIVOT = 'B' (Bottom pivot), the rotation is
+*  performed for the plane (k,z), giving P(k) the form
+*  
+*     P(k) = ( 1                                             )
+*            (      ...                                      )
+*            (             1                                 )
+*            (                  c(k)                    s(k) )
+*            (                         1                     )
+*            (                              ...              )
+*            (                                     1         )
+*            (                 -s(k)                    c(k) )
+*  
+*  where R(k) appears in rows and columns k and z.  The rotations are
+*  performed without ever forming P(k) explicitly.
 *
 *  Arguments
 *  =========
@@ -62,13 +94,7 @@
 *          Specifies whether the plane rotation matrix P is applied to
 *          A on the left or the right.
 *          = 'L':  Left, compute A := P*A
-*          = '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 )
+*          = 'R':  Right, compute A:= A*P**T
 *
 *  PIVOT   (input) CHARACTER*1
 *          Specifies the plane for which P(k) is a plane rotation
@@ -77,6 +103,12 @@
 *          = 'T':  Top pivot, the plane (1,k+1)
 *          = 'B':  Bottom pivot, the plane (k,z)
 *
+*  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)
+*
 *  M       (input) INTEGER
 *          The number of rows of the matrix A.  If m <= 1, an immediate
 *          return is effected.
@@ -85,18 +117,22 @@
 *          The number of columns of the matrix A.  If n <= 1, an
 *          immediate return is effected.
 *
-*  C, S    (input) DOUBLE PRECISION arrays, dimension
+*  C       (input) DOUBLE PRECISION array, dimension
+*                  (M-1) if SIDE = 'L'
+*                  (N-1) if SIDE = 'R'
+*          The cosines c(k) of the plane rotations.
+*
+*  S       (input) DOUBLE PRECISION array, 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 ) )
+*          The sines s(k) of the plane rotations.  The 2-by-2 plane
+*          rotation part of the matrix P(k), R(k), has the form
+*          R(k) = (  c(k)  s(k) )
+*                 ( -s(k)  c(k) ).
 *
 *  A       (input/output) DOUBLE PRECISION 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'.
+*          The M-by-N matrix A.  On exit, A is overwritten by P*A if
+*          SIDE = 'R' or by A*P**T if SIDE = 'L'.
 *
 *  LDA     (input) INTEGER
 *          The leading dimension of the array A.  LDA >= max(1,M).