diff options
author | jofret | 2009-04-28 07:17:00 +0000 |
---|---|---|
committer | jofret | 2009-04-28 07:17:00 +0000 |
commit | 8c8d2f518968ce7057eec6aa5cd5aec8faab861a (patch) | |
tree | 3dd1788b71d6a3ce2b73d2d475a3133580e17530 /src/lib/lapack/zlatrz.f | |
parent | 9f652ffc16a310ac6641a9766c5b9e2671e0e9cb (diff) | |
download | scilab2c-8c8d2f518968ce7057eec6aa5cd5aec8faab861a.tar.gz scilab2c-8c8d2f518968ce7057eec6aa5cd5aec8faab861a.tar.bz2 scilab2c-8c8d2f518968ce7057eec6aa5cd5aec8faab861a.zip |
Moving lapack to right place
Diffstat (limited to 'src/lib/lapack/zlatrz.f')
-rw-r--r-- | src/lib/lapack/zlatrz.f | 133 |
1 files changed, 0 insertions, 133 deletions
diff --git a/src/lib/lapack/zlatrz.f b/src/lib/lapack/zlatrz.f deleted file mode 100644 index c1c7aab3..00000000 --- a/src/lib/lapack/zlatrz.f +++ /dev/null @@ -1,133 +0,0 @@ - SUBROUTINE ZLATRZ( M, N, L, A, LDA, TAU, WORK ) -* -* -- LAPACK routine (version 3.1) -- -* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. -* November 2006 -* -* .. Scalar Arguments .. - INTEGER L, LDA, M, N -* .. -* .. Array Arguments .. - COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) -* .. -* -* Purpose -* ======= -* -* ZLATRZ factors the M-by-(M+L) complex upper trapezoidal matrix -* [ A1 A2 ] = [ A(1:M,1:M) A(1:M,N-L+1:N) ] as ( R 0 ) * Z by means -* of unitary transformations, where Z is an (M+L)-by-(M+L) unitary -* matrix and, R and A1 are M-by-M upper triangular matrices. -* -* Arguments -* ========= -* -* M (input) INTEGER -* The number of rows of the matrix A. M >= 0. -* -* N (input) INTEGER -* The number of columns of the matrix A. N >= 0. -* -* L (input) INTEGER -* The number of columns of the matrix A containing the -* meaningful part of the Householder vectors. N-M >= L >= 0. -* -* A (input/output) COMPLEX*16 array, dimension (LDA,N) -* On entry, the leading M-by-N upper trapezoidal part of the -* array A must contain the matrix to be factorized. -* On exit, the leading M-by-M upper triangular part of A -* contains the upper triangular matrix R, and elements N-L+1 to -* N of the first M rows of A, with the array TAU, represent the -* unitary matrix Z as a product of M elementary reflectors. -* -* LDA (input) INTEGER -* The leading dimension of the array A. LDA >= max(1,M). -* -* TAU (output) COMPLEX*16 array, dimension (M) -* The scalar factors of the elementary reflectors. -* -* WORK (workspace) COMPLEX*16 array, dimension (M) -* -* Further Details -* =============== -* -* Based on contributions by -* A. Petitet, Computer Science Dept., Univ. of Tenn., Knoxville, USA -* -* The factorization is obtained by Householder's method. The kth -* transformation matrix, Z( k ), which is used to introduce zeros into -* the ( m - k + 1 )th row of A, is given in the form -* -* Z( k ) = ( I 0 ), -* ( 0 T( k ) ) -* -* where -* -* T( k ) = I - tau*u( k )*u( k )', u( k ) = ( 1 ), -* ( 0 ) -* ( z( k ) ) -* -* tau is a scalar and z( k ) is an l element vector. tau and z( k ) -* are chosen to annihilate the elements of the kth row of A2. -* -* The scalar tau is returned in the kth element of TAU and the vector -* u( k ) in the kth row of A2, such that the elements of z( k ) are -* in a( k, l + 1 ), ..., a( k, n ). The elements of R are returned in -* the upper triangular part of A1. -* -* Z is given by -* -* Z = Z( 1 ) * Z( 2 ) * ... * Z( m ). -* -* ===================================================================== -* -* .. Parameters .. - COMPLEX*16 ZERO - PARAMETER ( ZERO = ( 0.0D+0, 0.0D+0 ) ) -* .. -* .. Local Scalars .. - INTEGER I - COMPLEX*16 ALPHA -* .. -* .. External Subroutines .. - EXTERNAL ZLACGV, ZLARFG, ZLARZ -* .. -* .. Intrinsic Functions .. - INTRINSIC DCONJG -* .. -* .. Executable Statements .. -* -* Quick return if possible -* - IF( M.EQ.0 ) THEN - RETURN - ELSE IF( M.EQ.N ) THEN - DO 10 I = 1, N - TAU( I ) = ZERO - 10 CONTINUE - RETURN - END IF -* - DO 20 I = M, 1, -1 -* -* Generate elementary reflector H(i) to annihilate -* [ A(i,i) A(i,n-l+1:n) ] -* - CALL ZLACGV( L, A( I, N-L+1 ), LDA ) - ALPHA = DCONJG( A( I, I ) ) - CALL ZLARFG( L+1, ALPHA, A( I, N-L+1 ), LDA, TAU( I ) ) - TAU( I ) = DCONJG( TAU( I ) ) -* -* Apply H(i) to A(1:i-1,i:n) from the right -* - CALL ZLARZ( 'Right', I-1, N-I+1, L, A( I, N-L+1 ), LDA, - $ DCONJG( TAU( I ) ), A( 1, I ), LDA, WORK ) - A( I, I ) = DCONJG( ALPHA ) -* - 20 CONTINUE -* - RETURN -* -* End of ZLATRZ -* - END |