LAPACK 3.3.1
Linear Algebra PACKage

srqt03.f

Go to the documentation of this file.
00001       SUBROUTINE SRQT03( M, N, K, AF, C, CC, Q, LDA, TAU, WORK, LWORK,
00002      $                   RWORK, RESULT )
00003 *
00004 *  -- LAPACK test routine (version 3.1) --
00005 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
00006 *     November 2006
00007 *
00008 *     .. Scalar Arguments ..
00009       INTEGER            K, LDA, LWORK, M, N
00010 *     ..
00011 *     .. Array Arguments ..
00012       REAL               AF( LDA, * ), C( LDA, * ), CC( LDA, * ),
00013      $                   Q( LDA, * ), RESULT( * ), RWORK( * ), TAU( * ),
00014      $                   WORK( LWORK )
00015 *     ..
00016 *
00017 *  Purpose
00018 *  =======
00019 *
00020 *  SRQT03 tests SORMRQ, which computes Q*C, Q'*C, C*Q or C*Q'.
00021 *
00022 *  SRQT03 compares the results of a call to SORMRQ with the results of
00023 *  forming Q explicitly by a call to SORGRQ and then performing matrix
00024 *  multiplication by a call to SGEMM.
00025 *
00026 *  Arguments
00027 *  =========
00028 *
00029 *  M       (input) INTEGER
00030 *          The number of rows or columns of the matrix C; C is n-by-m if
00031 *          Q is applied from the left, or m-by-n if Q is applied from
00032 *          the right.  M >= 0.
00033 *
00034 *  N       (input) INTEGER
00035 *          The order of the orthogonal matrix Q.  N >= 0.
00036 *
00037 *  K       (input) INTEGER
00038 *          The number of elementary reflectors whose product defines the
00039 *          orthogonal matrix Q.  N >= K >= 0.
00040 *
00041 *  AF      (input) REAL array, dimension (LDA,N)
00042 *          Details of the RQ factorization of an m-by-n matrix, as
00043 *          returned by SGERQF. See SGERQF for further details.
00044 *
00045 *  C       (workspace) REAL array, dimension (LDA,N)
00046 *
00047 *  CC      (workspace) REAL array, dimension (LDA,N)
00048 *
00049 *  Q       (workspace) REAL array, dimension (LDA,N)
00050 *
00051 *  LDA     (input) INTEGER
00052 *          The leading dimension of the arrays AF, C, CC, and Q.
00053 *
00054 *  TAU     (input) REAL array, dimension (min(M,N))
00055 *          The scalar factors of the elementary reflectors corresponding
00056 *          to the RQ factorization in AF.
00057 *
00058 *  WORK    (workspace) REAL array, dimension (LWORK)
00059 *
00060 *  LWORK   (input) INTEGER
00061 *          The length of WORK.  LWORK must be at least M, and should be
00062 *          M*NB, where NB is the blocksize for this environment.
00063 *
00064 *  RWORK   (workspace) REAL array, dimension (M)
00065 *
00066 *  RESULT  (output) REAL array, dimension (4)
00067 *          The test ratios compare two techniques for multiplying a
00068 *          random matrix C by an n-by-n orthogonal matrix Q.
00069 *          RESULT(1) = norm( Q*C - Q*C )  / ( N * norm(C) * EPS )
00070 *          RESULT(2) = norm( C*Q - C*Q )  / ( N * norm(C) * EPS )
00071 *          RESULT(3) = norm( Q'*C - Q'*C )/ ( N * norm(C) * EPS )
00072 *          RESULT(4) = norm( C*Q' - C*Q' )/ ( N * norm(C) * EPS )
00073 *
00074 *  =====================================================================
00075 *
00076 *     .. Parameters ..
00077       REAL               ZERO, ONE
00078       PARAMETER          ( ZERO = 0.0E0, ONE = 1.0E0 )
00079       REAL               ROGUE
00080       PARAMETER          ( ROGUE = -1.0E+10 )
00081 *     ..
00082 *     .. Local Scalars ..
00083       CHARACTER          SIDE, TRANS
00084       INTEGER            INFO, ISIDE, ITRANS, J, MC, MINMN, NC
00085       REAL               CNORM, EPS, RESID
00086 *     ..
00087 *     .. External Functions ..
00088       LOGICAL            LSAME
00089       REAL               SLAMCH, SLANGE
00090       EXTERNAL           LSAME, SLAMCH, SLANGE
00091 *     ..
00092 *     .. External Subroutines ..
00093       EXTERNAL           SGEMM, SLACPY, SLARNV, SLASET, SORGRQ, SORMRQ
00094 *     ..
00095 *     .. Local Arrays ..
00096       INTEGER            ISEED( 4 )
00097 *     ..
00098 *     .. Intrinsic Functions ..
00099       INTRINSIC          MAX, MIN, REAL
00100 *     ..
00101 *     .. Scalars in Common ..
00102       CHARACTER*32       SRNAMT
00103 *     ..
00104 *     .. Common blocks ..
00105       COMMON             / SRNAMC / SRNAMT
00106 *     ..
00107 *     .. Data statements ..
00108       DATA               ISEED / 1988, 1989, 1990, 1991 /
00109 *     ..
00110 *     .. Executable Statements ..
00111 *
00112       EPS = SLAMCH( 'Epsilon' )
00113       MINMN = MIN( M, N )
00114 *
00115 *     Quick return if possible
00116 *
00117       IF( MINMN.EQ.0 ) THEN
00118          RESULT( 1 ) = ZERO
00119          RESULT( 2 ) = ZERO
00120          RESULT( 3 ) = ZERO
00121          RESULT( 4 ) = ZERO
00122          RETURN
00123       END IF
00124 *
00125 *     Copy the last k rows of the factorization to the array Q
00126 *
00127       CALL SLASET( 'Full', N, N, ROGUE, ROGUE, Q, LDA )
00128       IF( K.GT.0 .AND. N.GT.K )
00129      $   CALL SLACPY( 'Full', K, N-K, AF( M-K+1, 1 ), LDA,
00130      $                Q( N-K+1, 1 ), LDA )
00131       IF( K.GT.1 )
00132      $   CALL SLACPY( 'Lower', K-1, K-1, AF( M-K+2, N-K+1 ), LDA,
00133      $                Q( N-K+2, N-K+1 ), LDA )
00134 *
00135 *     Generate the n-by-n matrix Q
00136 *
00137       SRNAMT = 'SORGRQ'
00138       CALL SORGRQ( N, N, K, Q, LDA, TAU( MINMN-K+1 ), WORK, LWORK,
00139      $             INFO )
00140 *
00141       DO 30 ISIDE = 1, 2
00142          IF( ISIDE.EQ.1 ) THEN
00143             SIDE = 'L'
00144             MC = N
00145             NC = M
00146          ELSE
00147             SIDE = 'R'
00148             MC = M
00149             NC = N
00150          END IF
00151 *
00152 *        Generate MC by NC matrix C
00153 *
00154          DO 10 J = 1, NC
00155             CALL SLARNV( 2, ISEED, MC, C( 1, J ) )
00156    10    CONTINUE
00157          CNORM = SLANGE( '1', MC, NC, C, LDA, RWORK )
00158          IF( CNORM.EQ.0.0 )
00159      $      CNORM = ONE
00160 *
00161          DO 20 ITRANS = 1, 2
00162             IF( ITRANS.EQ.1 ) THEN
00163                TRANS = 'N'
00164             ELSE
00165                TRANS = 'T'
00166             END IF
00167 *
00168 *           Copy C
00169 *
00170             CALL SLACPY( 'Full', MC, NC, C, LDA, CC, LDA )
00171 *
00172 *           Apply Q or Q' to C
00173 *
00174             SRNAMT = 'SORMRQ'
00175             IF( K.GT.0 )
00176      $         CALL SORMRQ( SIDE, TRANS, MC, NC, K, AF( M-K+1, 1 ), LDA,
00177      $                      TAU( MINMN-K+1 ), CC, LDA, WORK, LWORK,
00178      $                      INFO )
00179 *
00180 *           Form explicit product and subtract
00181 *
00182             IF( LSAME( SIDE, 'L' ) ) THEN
00183                CALL SGEMM( TRANS, 'No transpose', MC, NC, MC, -ONE, Q,
00184      $                     LDA, C, LDA, ONE, CC, LDA )
00185             ELSE
00186                CALL SGEMM( 'No transpose', TRANS, MC, NC, NC, -ONE, C,
00187      $                     LDA, Q, LDA, ONE, CC, LDA )
00188             END IF
00189 *
00190 *           Compute error in the difference
00191 *
00192             RESID = SLANGE( '1', MC, NC, CC, LDA, RWORK )
00193             RESULT( ( ISIDE-1 )*2+ITRANS ) = RESID /
00194      $         ( REAL( MAX( 1, N ) )*CNORM*EPS )
00195 *
00196    20    CONTINUE
00197    30 CONTINUE
00198 *
00199       RETURN
00200 *
00201 *     End of SRQT03
00202 *
00203       END
 All Files Functions