LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
real function cqpt01 ( integer  M,
integer  N,
integer  K,
complex, dimension( lda, * )  A,
complex, dimension( lda, * )  AF,
integer  LDA,
complex, dimension( * )  TAU,
integer, dimension( * )  JPVT,
complex, dimension( lwork )  WORK,
integer  LWORK 
)

CQPT01

Purpose:
 CQPT01 tests the QR-factorization with pivoting of a matrix A.  The
 array AF contains the (possibly partial) QR-factorization of A, where
 the upper triangle of AF(1:k,1:k) is a partial triangular factor,
 the entries below the diagonal in the first k columns are the
 Householder vectors, and the rest of AF contains a partially updated
 matrix.

 This function returns ||A*P - Q*R||/(||norm(A)||*eps*M)
Parameters
[in]M
          M is INTEGER
          The number of rows of the matrices A and AF.
[in]N
          N is INTEGER
          The number of columns of the matrices A and AF.
[in]K
          K is INTEGER
          The number of columns of AF that have been reduced
          to upper triangular form.
[in]A
          A is COMPLEX array, dimension (LDA, N)
          The original matrix A.
[in]AF
          AF is COMPLEX array, dimension (LDA,N)
          The (possibly partial) output of CGEQPF.  The upper triangle
          of AF(1:k,1:k) is a partial triangular factor, the entries
          below the diagonal in the first k columns are the Householder
          vectors, and the rest of AF contains a partially updated
          matrix.
[in]LDA
          LDA is INTEGER
          The leading dimension of the arrays A and AF.
[in]TAU
          TAU is COMPLEX array, dimension (K)
          Details of the Householder transformations as returned by
          CGEQPF.
[in]JPVT
          JPVT is INTEGER array, dimension (N)
          Pivot information as returned by CGEQPF.
[out]WORK
          WORK is COMPLEX array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          The length of the array WORK.  LWORK >= M*N+N.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 122 of file cqpt01.f.

122 *
123 * -- LAPACK test routine (version 3.4.0) --
124 * -- LAPACK is a software package provided by Univ. of Tennessee, --
125 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
126 * November 2011
127 *
128 * .. Scalar Arguments ..
129  INTEGER k, lda, lwork, m, n
130 * ..
131 * .. Array Arguments ..
132  INTEGER jpvt( * )
133  COMPLEX a( lda, * ), af( lda, * ), tau( * ),
134  $ work( lwork )
135 * ..
136 *
137 * =====================================================================
138 *
139 * .. Parameters ..
140  REAL zero, one
141  parameter ( zero = 0.0e0, one = 1.0e0 )
142 * ..
143 * .. Local Scalars ..
144  INTEGER i, info, j
145  REAL norma
146 * ..
147 * .. Local Arrays ..
148  REAL rwork( 1 )
149 * ..
150 * .. External Functions ..
151  REAL clange, slamch
152  EXTERNAL clange, slamch
153 * ..
154 * .. External Subroutines ..
155  EXTERNAL caxpy, ccopy, cunmqr, xerbla
156 * ..
157 * .. Intrinsic Functions ..
158  INTRINSIC cmplx, max, min, real
159 * ..
160 * .. Executable Statements ..
161 *
162  cqpt01 = zero
163 *
164 * Test if there is enough workspace
165 *
166  IF( lwork.LT.m*n+n ) THEN
167  CALL xerbla( 'CQPT01', 10 )
168  RETURN
169  END IF
170 *
171 * Quick return if possible
172 *
173  IF( m.LE.0 .OR. n.LE.0 )
174  $ RETURN
175 *
176  norma = clange( 'One-norm', m, n, a, lda, rwork )
177 *
178  DO 30 j = 1, k
179  DO 10 i = 1, min( j, m )
180  work( ( j-1 )*m+i ) = af( i, j )
181  10 CONTINUE
182  DO 20 i = j + 1, m
183  work( ( j-1 )*m+i ) = zero
184  20 CONTINUE
185  30 CONTINUE
186  DO 40 j = k + 1, n
187  CALL ccopy( m, af( 1, j ), 1, work( ( j-1 )*m+1 ), 1 )
188  40 CONTINUE
189 *
190  CALL cunmqr( 'Left', 'No transpose', m, n, k, af, lda, tau, work,
191  $ m, work( m*n+1 ), lwork-m*n, info )
192 *
193  DO 50 j = 1, n
194 *
195 * Compare i-th column of QR and jpvt(i)-th column of A
196 *
197  CALL caxpy( m, cmplx( -one ), a( 1, jpvt( j ) ), 1,
198  $ work( ( j-1 )*m+1 ), 1 )
199  50 CONTINUE
200 *
201  cqpt01 = clange( 'One-norm', m, n, work, m, rwork ) /
202  $ ( REAL( MAX( M, N ) )*slamch( 'Epsilon' ) )
203  IF( norma.NE.zero )
204  $ cqpt01 = cqpt01 / norma
205 *
206  RETURN
207 *
208 * End of CQPT01
209 *
real function cqpt01(M, N, K, A, AF, LDA, TAU, JPVT, WORK, LWORK)
CQPT01
Definition: cqpt01.f:122
real function clange(NORM, M, N, A, LDA, WORK)
CLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: clange.f:117
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cunmqr(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
CUNMQR
Definition: cunmqr.f:170
subroutine ccopy(N, CX, INCX, CY, INCY)
CCOPY
Definition: ccopy.f:52
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
subroutine caxpy(N, CA, CX, INCX, CY, INCY)
CAXPY
Definition: caxpy.f:53

Here is the call graph for this function: