summaryrefslogtreecommitdiff
path: root/TESTING/LIN/zqrt03.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/zqrt03.f
downloadlapack-baba851215b44ac3b60b9248eb02bcce7eb76247.tar.gz
lapack-baba851215b44ac3b60b9248eb02bcce7eb76247.tar.bz2
lapack-baba851215b44ac3b60b9248eb02bcce7eb76247.zip
Move LAPACK trunk into position.
Diffstat (limited to 'TESTING/LIN/zqrt03.f')
-rw-r--r--TESTING/LIN/zqrt03.f186
1 files changed, 186 insertions, 0 deletions
diff --git a/TESTING/LIN/zqrt03.f b/TESTING/LIN/zqrt03.f
new file mode 100644
index 00000000..8e239905
--- /dev/null
+++ b/TESTING/LIN/zqrt03.f
@@ -0,0 +1,186 @@
+ SUBROUTINE ZQRT03( M, N, K, AF, C, CC, Q, LDA, TAU, WORK, LWORK,
+ $ RWORK, RESULT )
+*
+* -- LAPACK test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ INTEGER K, LDA, LWORK, M, N
+* ..
+* .. Array Arguments ..
+ DOUBLE PRECISION RESULT( * ), RWORK( * )
+ COMPLEX*16 AF( LDA, * ), C( LDA, * ), CC( LDA, * ),
+ $ Q( LDA, * ), TAU( * ), WORK( LWORK )
+* ..
+*
+* Purpose
+* =======
+*
+* ZQRT03 tests ZUNMQR, which computes Q*C, Q'*C, C*Q or C*Q'.
+*
+* ZQRT03 compares the results of a call to ZUNMQR with the results of
+* forming Q explicitly by a call to ZUNGQR and then performing matrix
+* multiplication by a call to ZGEMM.
+*
+* Arguments
+* =========
+*
+* M (input) INTEGER
+* The order of the orthogonal matrix Q. M >= 0.
+*
+* N (input) INTEGER
+* The number of rows or columns of the matrix C; C is m-by-n if
+* Q is applied from the left, or n-by-m if Q is applied from
+* the right. N >= 0.
+*
+* K (input) INTEGER
+* The number of elementary reflectors whose product defines the
+* orthogonal matrix Q. M >= K >= 0.
+*
+* AF (input) COMPLEX*16 array, dimension (LDA,N)
+* Details of the QR factorization of an m-by-n matrix, as
+* returnedby ZGEQRF. See CGEQRF for further details.
+*
+* C (workspace) COMPLEX*16 array, dimension (LDA,N)
+*
+* CC (workspace) COMPLEX*16 array, dimension (LDA,N)
+*
+* Q (workspace) COMPLEX*16 array, dimension (LDA,M)
+*
+* LDA (input) INTEGER
+* The leading dimension of the arrays AF, C, CC, and Q.
+*
+* TAU (input) COMPLEX*16 array, dimension (min(M,N))
+* The scalar factors of the elementary reflectors corresponding
+* to the QR factorization in AF.
+*
+* WORK (workspace) COMPLEX*16 array, dimension (LWORK)
+*
+* LWORK (input) INTEGER
+* The length of WORK. LWORK must be at least M, and should be
+* M*NB, where NB is the blocksize for this environment.
+*
+* RWORK (workspace) DOUBLE PRECISION array, dimension (M)
+*
+* RESULT (output) DOUBLE PRECISION array, dimension (4)
+* The test ratios compare two techniques for multiplying a
+* random matrix C by an m-by-m orthogonal matrix Q.
+* RESULT(1) = norm( Q*C - Q*C ) / ( M * norm(C) * EPS )
+* RESULT(2) = norm( C*Q - C*Q ) / ( M * norm(C) * EPS )
+* RESULT(3) = norm( Q'*C - Q'*C )/ ( M * norm(C) * EPS )
+* RESULT(4) = norm( C*Q' - C*Q' )/ ( M * norm(C) * EPS )
+*
+* =====================================================================
+*
+* .. Parameters ..
+ DOUBLE PRECISION ZERO, ONE
+ PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
+ COMPLEX*16 ROGUE
+ PARAMETER ( ROGUE = ( -1.0D+10, -1.0D+10 ) )
+* ..
+* .. Local Scalars ..
+ CHARACTER SIDE, TRANS
+ INTEGER INFO, ISIDE, ITRANS, J, MC, NC
+ DOUBLE PRECISION CNORM, EPS, RESID
+* ..
+* .. External Functions ..
+ LOGICAL LSAME
+ DOUBLE PRECISION DLAMCH, ZLANGE
+ EXTERNAL LSAME, DLAMCH, ZLANGE
+* ..
+* .. External Subroutines ..
+ EXTERNAL ZGEMM, ZLACPY, ZLARNV, ZLASET, ZUNGQR, ZUNMQR
+* ..
+* .. Local Arrays ..
+ INTEGER ISEED( 4 )
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC DBLE, DCMPLX, MAX
+* ..
+* .. Scalars in Common ..
+ CHARACTER(32) SRNAMT
+* ..
+* .. Common blocks ..
+ COMMON / SRNAMC / SRNAMT
+* ..
+* .. Data statements ..
+ DATA ISEED / 1988, 1989, 1990, 1991 /
+* ..
+* .. Executable Statements ..
+*
+ EPS = DLAMCH( 'Epsilon' )
+*
+* Copy the first k columns of the factorization to the array Q
+*
+ CALL ZLASET( 'Full', M, M, ROGUE, ROGUE, Q, LDA )
+ CALL ZLACPY( 'Lower', M-1, K, AF( 2, 1 ), LDA, Q( 2, 1 ), LDA )
+*
+* Generate the m-by-m matrix Q
+*
+ SRNAMT = 'ZUNGQR'
+ CALL ZUNGQR( M, M, K, Q, LDA, TAU, WORK, LWORK, INFO )
+*
+ DO 30 ISIDE = 1, 2
+ IF( ISIDE.EQ.1 ) THEN
+ SIDE = 'L'
+ MC = M
+ NC = N
+ ELSE
+ SIDE = 'R'
+ MC = N
+ NC = M
+ END IF
+*
+* Generate MC by NC matrix C
+*
+ DO 10 J = 1, NC
+ CALL ZLARNV( 2, ISEED, MC, C( 1, J ) )
+ 10 CONTINUE
+ CNORM = ZLANGE( '1', MC, NC, C, LDA, RWORK )
+ IF( CNORM.EQ.ZERO )
+ $ CNORM = ONE
+*
+ DO 20 ITRANS = 1, 2
+ IF( ITRANS.EQ.1 ) THEN
+ TRANS = 'N'
+ ELSE
+ TRANS = 'C'
+ END IF
+*
+* Copy C
+*
+ CALL ZLACPY( 'Full', MC, NC, C, LDA, CC, LDA )
+*
+* Apply Q or Q' to C
+*
+ SRNAMT = 'ZUNMQR'
+ CALL ZUNMQR( SIDE, TRANS, MC, NC, K, AF, LDA, TAU, CC, LDA,
+ $ WORK, LWORK, INFO )
+*
+* Form explicit product and subtract
+*
+ IF( LSAME( SIDE, 'L' ) ) THEN
+ CALL ZGEMM( TRANS, 'No transpose', MC, NC, MC,
+ $ DCMPLX( -ONE ), Q, LDA, C, LDA,
+ $ DCMPLX( ONE ), CC, LDA )
+ ELSE
+ CALL ZGEMM( 'No transpose', TRANS, MC, NC, NC,
+ $ DCMPLX( -ONE ), C, LDA, Q, LDA,
+ $ DCMPLX( ONE ), CC, LDA )
+ END IF
+*
+* Compute error in the difference
+*
+ RESID = ZLANGE( '1', MC, NC, CC, LDA, RWORK )
+ RESULT( ( ISIDE-1 )*2+ITRANS ) = RESID /
+ $ ( DBLE( MAX( 1, M ) )*CNORM*EPS )
+*
+ 20 CONTINUE
+ 30 CONTINUE
+*
+ RETURN
+*
+* End of ZQRT03
+*
+ END