summaryrefslogtreecommitdiff
path: root/TESTING/LIN/zlatsy.f
diff options
context:
space:
mode:
authorjason <jason@8a072113-8704-0410-8d35-dd094bca7971>2008-10-28 01:38:50 +0000
committerjason <jason@8a072113-8704-0410-8d35-dd094bca7971>2008-10-28 01:38:50 +0000
commitbaba851215b44ac3b60b9248eb02bcce7eb76247 (patch)
tree8c0f5c006875532a30d4409f5e94b0f310ff00a7 /TESTING/LIN/zlatsy.f
downloadlapack-baba851215b44ac3b60b9248eb02bcce7eb76247.tar.gz
lapack-baba851215b44ac3b60b9248eb02bcce7eb76247.tar.bz2
lapack-baba851215b44ac3b60b9248eb02bcce7eb76247.zip
Move LAPACK trunk into position.
Diffstat (limited to 'TESTING/LIN/zlatsy.f')
-rw-r--r--TESTING/LIN/zlatsy.f207
1 files changed, 207 insertions, 0 deletions
diff --git a/TESTING/LIN/zlatsy.f b/TESTING/LIN/zlatsy.f
new file mode 100644
index 00000000..82abb7e2
--- /dev/null
+++ b/TESTING/LIN/zlatsy.f
@@ -0,0 +1,207 @@
+ SUBROUTINE ZLATSY( UPLO, N, X, LDX, ISEED )
+*
+* -- LAPACK auxiliary test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ CHARACTER UPLO
+ INTEGER LDX, N
+* ..
+* .. Array Arguments ..
+ INTEGER ISEED( * )
+ COMPLEX*16 X( LDX, * )
+* ..
+*
+* Purpose
+* =======
+*
+* ZLATSY generates a special test matrix for the complex symmetric
+* (indefinite) factorization. The pivot blocks of the generated matrix
+* will be in the following order:
+* 2x2 pivot block, non diagonalizable
+* 1x1 pivot block
+* 2x2 pivot block, diagonalizable
+* (cycle repeats)
+* A row interchange is required for each non-diagonalizable 2x2 block.
+*
+* Arguments
+* =========
+*
+* UPLO (input) CHARACTER
+* Specifies whether the generated matrix is to be upper or
+* lower triangular.
+* = 'U': Upper triangular
+* = 'L': Lower triangular
+*
+* N (input) INTEGER
+* The dimension of the matrix to be generated.
+*
+* X (output) COMPLEX*16 array, dimension (LDX,N)
+* The generated matrix, consisting of 3x3 and 2x2 diagonal
+* blocks which result in the pivot sequence given above.
+* The matrix outside of these diagonal blocks is zero.
+*
+* LDX (input) INTEGER
+* The leading dimension of the array X.
+*
+* ISEED (input/output) INTEGER array, dimension (4)
+* On entry, the seed for the random number generator. The last
+* of the four integers must be odd. (modified on exit)
+*
+* =====================================================================
+*
+* .. Parameters ..
+ COMPLEX*16 EYE
+ PARAMETER ( EYE = ( 0.0D0, 1.0D0 ) )
+* ..
+* .. Local Scalars ..
+ INTEGER I, J, N5
+ DOUBLE PRECISION ALPHA, ALPHA3, BETA
+ COMPLEX*16 A, B, C, R
+* ..
+* .. External Functions ..
+ COMPLEX*16 ZLARND
+ EXTERNAL ZLARND
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC ABS, SQRT
+* ..
+* .. Executable Statements ..
+*
+* Initialize constants
+*
+ ALPHA = ( 1.D0+SQRT( 17.D0 ) ) / 8.D0
+ BETA = ALPHA - 1.D0 / 1000.D0
+ ALPHA3 = ALPHA*ALPHA*ALPHA
+*
+* UPLO = 'U': Upper triangular storage
+*
+ IF( UPLO.EQ.'U' ) THEN
+*
+* Fill the upper triangle of the matrix with zeros.
+*
+ DO 20 J = 1, N
+ DO 10 I = 1, J
+ X( I, J ) = 0.0D0
+ 10 CONTINUE
+ 20 CONTINUE
+ N5 = N / 5
+ N5 = N - 5*N5 + 1
+*
+ DO 30 I = N, N5, -5
+ A = ALPHA3*ZLARND( 5, ISEED )
+ B = ZLARND( 5, ISEED ) / ALPHA
+ C = A - 2.D0*B*EYE
+ R = C / BETA
+ X( I, I ) = A
+ X( I-2, I ) = B
+ X( I-2, I-1 ) = R
+ X( I-2, I-2 ) = C
+ X( I-1, I-1 ) = ZLARND( 2, ISEED )
+ X( I-3, I-3 ) = ZLARND( 2, ISEED )
+ X( I-4, I-4 ) = ZLARND( 2, ISEED )
+ IF( ABS( X( I-3, I-3 ) ).GT.ABS( X( I-4, I-4 ) ) ) THEN
+ X( I-4, I-3 ) = 2.0D0*X( I-3, I-3 )
+ ELSE
+ X( I-4, I-3 ) = 2.0D0*X( I-4, I-4 )
+ END IF
+ 30 CONTINUE
+*
+* Clean-up for N not a multiple of 5.
+*
+ I = N5 - 1
+ IF( I.GT.2 ) THEN
+ A = ALPHA3*ZLARND( 5, ISEED )
+ B = ZLARND( 5, ISEED ) / ALPHA
+ C = A - 2.D0*B*EYE
+ R = C / BETA
+ X( I, I ) = A
+ X( I-2, I ) = B
+ X( I-2, I-1 ) = R
+ X( I-2, I-2 ) = C
+ X( I-1, I-1 ) = ZLARND( 2, ISEED )
+ I = I - 3
+ END IF
+ IF( I.GT.1 ) THEN
+ X( I, I ) = ZLARND( 2, ISEED )
+ X( I-1, I-1 ) = ZLARND( 2, ISEED )
+ IF( ABS( X( I, I ) ).GT.ABS( X( I-1, I-1 ) ) ) THEN
+ X( I-1, I ) = 2.0D0*X( I, I )
+ ELSE
+ X( I-1, I ) = 2.0D0*X( I-1, I-1 )
+ END IF
+ I = I - 2
+ ELSE IF( I.EQ.1 ) THEN
+ X( I, I ) = ZLARND( 2, ISEED )
+ I = I - 1
+ END IF
+*
+* UPLO = 'L': Lower triangular storage
+*
+ ELSE
+*
+* Fill the lower triangle of the matrix with zeros.
+*
+ DO 50 J = 1, N
+ DO 40 I = J, N
+ X( I, J ) = 0.0D0
+ 40 CONTINUE
+ 50 CONTINUE
+ N5 = N / 5
+ N5 = N5*5
+*
+ DO 60 I = 1, N5, 5
+ A = ALPHA3*ZLARND( 5, ISEED )
+ B = ZLARND( 5, ISEED ) / ALPHA
+ C = A - 2.D0*B*EYE
+ R = C / BETA
+ X( I, I ) = A
+ X( I+2, I ) = B
+ X( I+2, I+1 ) = R
+ X( I+2, I+2 ) = C
+ X( I+1, I+1 ) = ZLARND( 2, ISEED )
+ X( I+3, I+3 ) = ZLARND( 2, ISEED )
+ X( I+4, I+4 ) = ZLARND( 2, ISEED )
+ IF( ABS( X( I+3, I+3 ) ).GT.ABS( X( I+4, I+4 ) ) ) THEN
+ X( I+4, I+3 ) = 2.0D0*X( I+3, I+3 )
+ ELSE
+ X( I+4, I+3 ) = 2.0D0*X( I+4, I+4 )
+ END IF
+ 60 CONTINUE
+*
+* Clean-up for N not a multiple of 5.
+*
+ I = N5 + 1
+ IF( I.LT.N-1 ) THEN
+ A = ALPHA3*ZLARND( 5, ISEED )
+ B = ZLARND( 5, ISEED ) / ALPHA
+ C = A - 2.D0*B*EYE
+ R = C / BETA
+ X( I, I ) = A
+ X( I+2, I ) = B
+ X( I+2, I+1 ) = R
+ X( I+2, I+2 ) = C
+ X( I+1, I+1 ) = ZLARND( 2, ISEED )
+ I = I + 3
+ END IF
+ IF( I.LT.N ) THEN
+ X( I, I ) = ZLARND( 2, ISEED )
+ X( I+1, I+1 ) = ZLARND( 2, ISEED )
+ IF( ABS( X( I, I ) ).GT.ABS( X( I+1, I+1 ) ) ) THEN
+ X( I+1, I ) = 2.0D0*X( I, I )
+ ELSE
+ X( I+1, I ) = 2.0D0*X( I+1, I+1 )
+ END IF
+ I = I + 2
+ ELSE IF( I.EQ.N ) THEN
+ X( I, I ) = ZLARND( 2, ISEED )
+ I = I + 1
+ END IF
+ END IF
+*
+ RETURN
+*
+* End of ZLATSY
+*
+ END