LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sqpt01()

real function sqpt01 ( integer  M,
integer  N,
integer  K,
real, dimension( lda, * )  A,
real, dimension( lda, * )  AF,
integer  LDA,
real, dimension( * )  TAU,
integer, dimension( * )  JPVT,
real, dimension( lwork )  WORK,
integer  LWORK 
)

SQPT01

Purpose:
 SQPT01 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 REAL array, dimension (LDA, N)
          The original matrix A.
[in]AF
          AF is REAL array, dimension (LDA,N)
          The (possibly partial) output of SGEQPF.  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 REAL array, dimension (K)
          Details of the Householder transformations as returned by
          SGEQPF.
[in]JPVT
          JPVT is INTEGER array, dimension (N)
          Pivot information as returned by SGEQPF.
[out]WORK
          WORK is REAL 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.

Definition at line 118 of file sqpt01.f.

120*
121* -- LAPACK test routine --
122* -- LAPACK is a software package provided by Univ. of Tennessee, --
123* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
124*
125* .. Scalar Arguments ..
126 INTEGER K, LDA, LWORK, M, N
127* ..
128* .. Array Arguments ..
129 INTEGER JPVT( * )
130 REAL A( LDA, * ), AF( LDA, * ), TAU( * ),
131 $ WORK( LWORK )
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 REAL ZERO, ONE
138 parameter( zero = 0.0e0, one = 1.0e0 )
139* ..
140* .. Local Scalars ..
141 INTEGER I, INFO, J
142 REAL NORMA
143* ..
144* .. Local Arrays ..
145 REAL RWORK( 1 )
146* ..
147* .. External Functions ..
148 REAL SLAMCH, SLANGE
149 EXTERNAL slamch, slange
150* ..
151* .. External Subroutines ..
152 EXTERNAL saxpy, scopy, sormqr, xerbla
153* ..
154* .. Intrinsic Functions ..
155 INTRINSIC max, min, real
156* ..
157* .. Executable Statements ..
158*
159 sqpt01 = zero
160*
161* Test if there is enough workspace
162*
163 IF( lwork.LT.m*n+n ) THEN
164 CALL xerbla( 'SQPT01', 10 )
165 RETURN
166 END IF
167*
168* Quick return if possible
169*
170 IF( m.LE.0 .OR. n.LE.0 )
171 $ RETURN
172*
173 norma = slange( 'One-norm', m, n, a, lda, rwork )
174*
175 DO 30 j = 1, k
176 DO 10 i = 1, min( j, m )
177 work( ( j-1 )*m+i ) = af( i, j )
178 10 CONTINUE
179 DO 20 i = j + 1, m
180 work( ( j-1 )*m+i ) = zero
181 20 CONTINUE
182 30 CONTINUE
183 DO 40 j = k + 1, n
184 CALL scopy( m, af( 1, j ), 1, work( ( j-1 )*m+1 ), 1 )
185 40 CONTINUE
186*
187 CALL sormqr( 'Left', 'No transpose', m, n, k, af, lda, tau, work,
188 $ m, work( m*n+1 ), lwork-m*n, info )
189*
190 DO 50 j = 1, n
191*
192* Compare i-th column of QR and jpvt(i)-th column of A
193*
194 CALL saxpy( m, -one, a( 1, jpvt( j ) ), 1, work( ( j-1 )*m+1 ),
195 $ 1 )
196 50 CONTINUE
197*
198 sqpt01 = slange( 'One-norm', m, n, work, m, rwork ) /
199 $ ( real( max( m, n ) )*slamch( 'Epsilon' ) )
200 IF( norma.NE.zero )
201 $ sqpt01 = sqpt01 / norma
202*
203 RETURN
204*
205* End of SQPT01
206*
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
real function slange(NORM, M, N, A, LDA, WORK)
SLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: slange.f:114
subroutine sormqr(SIDE, TRANS, M, N, K, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
SORMQR
Definition: sormqr.f:168
subroutine scopy(N, SX, INCX, SY, INCY)
SCOPY
Definition: scopy.f:82
subroutine saxpy(N, SA, SX, INCX, SY, INCY)
SAXPY
Definition: saxpy.f:89
real function sqpt01(M, N, K, A, AF, LDA, TAU, JPVT, WORK, LWORK)
SQPT01
Definition: sqpt01.f:120
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:68
Here is the call graph for this function:
Here is the caller graph for this function: