1*> \brief \b ZQRT03 2* 3* =========== DOCUMENTATION =========== 4* 5* Online html documentation available at 6* http://www.netlib.org/lapack/explore-html/ 7* 8* Definition: 9* =========== 10* 11* SUBROUTINE ZQRT03( M, N, K, AF, C, CC, Q, LDA, TAU, WORK, LWORK, 12* RWORK, RESULT ) 13* 14* .. Scalar Arguments .. 15* INTEGER K, LDA, LWORK, M, N 16* .. 17* .. Array Arguments .. 18* DOUBLE PRECISION RESULT( * ), RWORK( * ) 19* COMPLEX*16 AF( LDA, * ), C( LDA, * ), CC( LDA, * ), 20* $ Q( LDA, * ), TAU( * ), WORK( LWORK ) 21* .. 22* 23* 24*> \par Purpose: 25* ============= 26*> 27*> \verbatim 28*> 29*> ZQRT03 tests ZUNMQR, which computes Q*C, Q'*C, C*Q or C*Q'. 30*> 31*> ZQRT03 compares the results of a call to ZUNMQR with the results of 32*> forming Q explicitly by a call to ZUNGQR and then performing matrix 33*> multiplication by a call to ZGEMM. 34*> \endverbatim 35* 36* Arguments: 37* ========== 38* 39*> \param[in] M 40*> \verbatim 41*> M is INTEGER 42*> The order of the orthogonal matrix Q. M >= 0. 43*> \endverbatim 44*> 45*> \param[in] N 46*> \verbatim 47*> N is INTEGER 48*> The number of rows or columns of the matrix C; C is m-by-n if 49*> Q is applied from the left, or n-by-m if Q is applied from 50*> the right. N >= 0. 51*> \endverbatim 52*> 53*> \param[in] K 54*> \verbatim 55*> K is INTEGER 56*> The number of elementary reflectors whose product defines the 57*> orthogonal matrix Q. M >= K >= 0. 58*> \endverbatim 59*> 60*> \param[in] AF 61*> \verbatim 62*> AF is COMPLEX*16 array, dimension (LDA,N) 63*> Details of the QR factorization of an m-by-n matrix, as 64*> returned by ZGEQRF. See ZGEQRF for further details. 65*> \endverbatim 66*> 67*> \param[out] C 68*> \verbatim 69*> C is COMPLEX*16 array, dimension (LDA,N) 70*> \endverbatim 71*> 72*> \param[out] CC 73*> \verbatim 74*> CC is COMPLEX*16 array, dimension (LDA,N) 75*> \endverbatim 76*> 77*> \param[out] Q 78*> \verbatim 79*> Q is COMPLEX*16 array, dimension (LDA,M) 80*> \endverbatim 81*> 82*> \param[in] LDA 83*> \verbatim 84*> LDA is INTEGER 85*> The leading dimension of the arrays AF, C, CC, and Q. 86*> \endverbatim 87*> 88*> \param[in] TAU 89*> \verbatim 90*> TAU is COMPLEX*16 array, dimension (min(M,N)) 91*> The scalar factors of the elementary reflectors corresponding 92*> to the QR factorization in AF. 93*> \endverbatim 94*> 95*> \param[out] WORK 96*> \verbatim 97*> WORK is COMPLEX*16 array, dimension (LWORK) 98*> \endverbatim 99*> 100*> \param[in] LWORK 101*> \verbatim 102*> LWORK is INTEGER 103*> The length of WORK. LWORK must be at least M, and should be 104*> M*NB, where NB is the blocksize for this environment. 105*> \endverbatim 106*> 107*> \param[out] RWORK 108*> \verbatim 109*> RWORK is DOUBLE PRECISION array, dimension (M) 110*> \endverbatim 111*> 112*> \param[out] RESULT 113*> \verbatim 114*> RESULT is DOUBLE PRECISION array, dimension (4) 115*> The test ratios compare two techniques for multiplying a 116*> random matrix C by an m-by-m orthogonal matrix Q. 117*> RESULT(1) = norm( Q*C - Q*C ) / ( M * norm(C) * EPS ) 118*> RESULT(2) = norm( C*Q - C*Q ) / ( M * norm(C) * EPS ) 119*> RESULT(3) = norm( Q'*C - Q'*C )/ ( M * norm(C) * EPS ) 120*> RESULT(4) = norm( C*Q' - C*Q' )/ ( M * norm(C) * EPS ) 121*> \endverbatim 122* 123* Authors: 124* ======== 125* 126*> \author Univ. of Tennessee 127*> \author Univ. of California Berkeley 128*> \author Univ. of Colorado Denver 129*> \author NAG Ltd. 130* 131*> \ingroup complex16_lin 132* 133* ===================================================================== 134 SUBROUTINE ZQRT03( M, N, K, AF, C, CC, Q, LDA, TAU, WORK, LWORK, 135 $ RWORK, RESULT ) 136* 137* -- LAPACK test routine -- 138* -- LAPACK is a software package provided by Univ. of Tennessee, -- 139* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..-- 140* 141* .. Scalar Arguments .. 142 INTEGER K, LDA, LWORK, M, N 143* .. 144* .. Array Arguments .. 145 DOUBLE PRECISION RESULT( * ), RWORK( * ) 146 COMPLEX*16 AF( LDA, * ), C( LDA, * ), CC( LDA, * ), 147 $ Q( LDA, * ), TAU( * ), WORK( LWORK ) 148* .. 149* 150* ===================================================================== 151* 152* .. Parameters .. 153 DOUBLE PRECISION ZERO, ONE 154 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 ) 155 COMPLEX*16 ROGUE 156 PARAMETER ( ROGUE = ( -1.0D+10, -1.0D+10 ) ) 157* .. 158* .. Local Scalars .. 159 CHARACTER SIDE, TRANS 160 INTEGER INFO, ISIDE, ITRANS, J, MC, NC 161 DOUBLE PRECISION CNORM, EPS, RESID 162* .. 163* .. External Functions .. 164 LOGICAL LSAME 165 DOUBLE PRECISION DLAMCH, ZLANGE 166 EXTERNAL LSAME, DLAMCH, ZLANGE 167* .. 168* .. External Subroutines .. 169 EXTERNAL ZGEMM, ZLACPY, ZLARNV, ZLASET, ZUNGQR, ZUNMQR 170* .. 171* .. Local Arrays .. 172 INTEGER ISEED( 4 ) 173* .. 174* .. Intrinsic Functions .. 175 INTRINSIC DBLE, DCMPLX, MAX 176* .. 177* .. Scalars in Common .. 178 CHARACTER*32 SRNAMT 179* .. 180* .. Common blocks .. 181 COMMON / SRNAMC / SRNAMT 182* .. 183* .. Data statements .. 184 DATA ISEED / 1988, 1989, 1990, 1991 / 185* .. 186* .. Executable Statements .. 187* 188 EPS = DLAMCH( 'Epsilon' ) 189* 190* Copy the first k columns of the factorization to the array Q 191* 192 CALL ZLASET( 'Full', M, M, ROGUE, ROGUE, Q, LDA ) 193 CALL ZLACPY( 'Lower', M-1, K, AF( 2, 1 ), LDA, Q( 2, 1 ), LDA ) 194* 195* Generate the m-by-m matrix Q 196* 197 SRNAMT = 'ZUNGQR' 198 CALL ZUNGQR( M, M, K, Q, LDA, TAU, WORK, LWORK, INFO ) 199* 200 DO 30 ISIDE = 1, 2 201 IF( ISIDE.EQ.1 ) THEN 202 SIDE = 'L' 203 MC = M 204 NC = N 205 ELSE 206 SIDE = 'R' 207 MC = N 208 NC = M 209 END IF 210* 211* Generate MC by NC matrix C 212* 213 DO 10 J = 1, NC 214 CALL ZLARNV( 2, ISEED, MC, C( 1, J ) ) 215 10 CONTINUE 216 CNORM = ZLANGE( '1', MC, NC, C, LDA, RWORK ) 217 IF( CNORM.EQ.ZERO ) 218 $ CNORM = ONE 219* 220 DO 20 ITRANS = 1, 2 221 IF( ITRANS.EQ.1 ) THEN 222 TRANS = 'N' 223 ELSE 224 TRANS = 'C' 225 END IF 226* 227* Copy C 228* 229 CALL ZLACPY( 'Full', MC, NC, C, LDA, CC, LDA ) 230* 231* Apply Q or Q' to C 232* 233 SRNAMT = 'ZUNMQR' 234 CALL ZUNMQR( SIDE, TRANS, MC, NC, K, AF, LDA, TAU, CC, LDA, 235 $ WORK, LWORK, INFO ) 236* 237* Form explicit product and subtract 238* 239 IF( LSAME( SIDE, 'L' ) ) THEN 240 CALL ZGEMM( TRANS, 'No transpose', MC, NC, MC, 241 $ DCMPLX( -ONE ), Q, LDA, C, LDA, 242 $ DCMPLX( ONE ), CC, LDA ) 243 ELSE 244 CALL ZGEMM( 'No transpose', TRANS, MC, NC, NC, 245 $ DCMPLX( -ONE ), C, LDA, Q, LDA, 246 $ DCMPLX( ONE ), CC, LDA ) 247 END IF 248* 249* Compute error in the difference 250* 251 RESID = ZLANGE( '1', MC, NC, CC, LDA, RWORK ) 252 RESULT( ( ISIDE-1 )*2+ITRANS ) = RESID / 253 $ ( DBLE( MAX( 1, M ) )*CNORM*EPS ) 254* 255 20 CONTINUE 256 30 CONTINUE 257* 258 RETURN 259* 260* End of ZQRT03 261* 262 END 263