LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine spot01 ( character  UPLO,
integer  N,
real, dimension( lda, * )  A,
integer  LDA,
real, dimension( ldafac, * )  AFAC,
integer  LDAFAC,
real, dimension( * )  RWORK,
real  RESID 
)

SPOT01

Purpose:
 SPOT01 reconstructs a symmetric positive definite matrix  A  from
 its L*L' or U'*U factorization and computes the residual
    norm( L*L' - A ) / ( N * norm(A) * EPS ) or
    norm( U'*U - A ) / ( N * norm(A) * EPS ),
 where EPS is the machine epsilon.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the upper or lower triangular part of the
          symmetric matrix A is stored:
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]N
          N is INTEGER
          The number of rows and columns of the matrix A.  N >= 0.
[in]A
          A is REAL array, dimension (LDA,N)
          The original symmetric matrix A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N)
[in,out]AFAC
          AFAC is REAL array, dimension (LDAFAC,N)
          On entry, the factor L or U from the L*L' or U'*U
          factorization of A.
          Overwritten with the reconstructed matrix, and then with the
          difference L*L' - A (or U'*U - A).
[in]LDAFAC
          LDAFAC is INTEGER
          The leading dimension of the array AFAC.  LDAFAC >= max(1,N).
[out]RWORK
          RWORK is REAL array, dimension (N)
[out]RESID
          RESID is REAL
          If UPLO = 'L', norm(L*L' - A) / ( N * norm(A) * EPS )
          If UPLO = 'U', norm(U'*U - A) / ( N * norm(A) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 106 of file spot01.f.

106 *
107 * -- LAPACK test routine (version 3.4.0) --
108 * -- LAPACK is a software package provided by Univ. of Tennessee, --
109 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
110 * November 2011
111 *
112 * .. Scalar Arguments ..
113  CHARACTER uplo
114  INTEGER lda, ldafac, n
115  REAL resid
116 * ..
117 * .. Array Arguments ..
118  REAL a( lda, * ), afac( ldafac, * ), rwork( * )
119 * ..
120 *
121 * =====================================================================
122 *
123 * .. Parameters ..
124  REAL zero, one
125  parameter ( zero = 0.0e+0, one = 1.0e+0 )
126 * ..
127 * .. Local Scalars ..
128  INTEGER i, j, k
129  REAL anorm, eps, t
130 * ..
131 * .. External Functions ..
132  LOGICAL lsame
133  REAL sdot, slamch, slansy
134  EXTERNAL lsame, sdot, slamch, slansy
135 * ..
136 * .. External Subroutines ..
137  EXTERNAL sscal, ssyr, strmv
138 * ..
139 * .. Intrinsic Functions ..
140  INTRINSIC real
141 * ..
142 * .. Executable Statements ..
143 *
144 * Quick exit if N = 0.
145 *
146  IF( n.LE.0 ) THEN
147  resid = zero
148  RETURN
149  END IF
150 *
151 * Exit with RESID = 1/EPS if ANORM = 0.
152 *
153  eps = slamch( 'Epsilon' )
154  anorm = slansy( '1', uplo, n, a, lda, rwork )
155  IF( anorm.LE.zero ) THEN
156  resid = one / eps
157  RETURN
158  END IF
159 *
160 * Compute the product U'*U, overwriting U.
161 *
162  IF( lsame( uplo, 'U' ) ) THEN
163  DO 10 k = n, 1, -1
164 *
165 * Compute the (K,K) element of the result.
166 *
167  t = sdot( k, afac( 1, k ), 1, afac( 1, k ), 1 )
168  afac( k, k ) = t
169 *
170 * Compute the rest of column K.
171 *
172  CALL strmv( 'Upper', 'Transpose', 'Non-unit', k-1, afac,
173  $ ldafac, afac( 1, k ), 1 )
174 *
175  10 CONTINUE
176 *
177 * Compute the product L*L', overwriting L.
178 *
179  ELSE
180  DO 20 k = n, 1, -1
181 *
182 * Add a multiple of column K of the factor L to each of
183 * columns K+1 through N.
184 *
185  IF( k+1.LE.n )
186  $ CALL ssyr( 'Lower', n-k, one, afac( k+1, k ), 1,
187  $ afac( k+1, k+1 ), ldafac )
188 *
189 * Scale column K by the diagonal element.
190 *
191  t = afac( k, k )
192  CALL sscal( n-k+1, t, afac( k, k ), 1 )
193 *
194  20 CONTINUE
195  END IF
196 *
197 * Compute the difference L*L' - A (or U'*U - A).
198 *
199  IF( lsame( uplo, 'U' ) ) THEN
200  DO 40 j = 1, n
201  DO 30 i = 1, j
202  afac( i, j ) = afac( i, j ) - a( i, j )
203  30 CONTINUE
204  40 CONTINUE
205  ELSE
206  DO 60 j = 1, n
207  DO 50 i = j, n
208  afac( i, j ) = afac( i, j ) - a( i, j )
209  50 CONTINUE
210  60 CONTINUE
211  END IF
212 *
213 * Compute norm( L*U - A ) / ( N * norm(A) * EPS )
214 *
215  resid = slansy( '1', uplo, n, afac, ldafac, rwork )
216 *
217  resid = ( ( resid / REAL( N ) ) / anorm ) / eps
218 *
219  RETURN
220 *
221 * End of SPOT01
222 *
real function sdot(N, SX, INCX, SY, INCY)
SDOT
Definition: sdot.f:53
subroutine strmv(UPLO, TRANS, DIAG, N, A, LDA, X, INCX)
STRMV
Definition: strmv.f:149
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
subroutine ssyr(UPLO, N, ALPHA, X, INCX, A, LDA)
SSYR
Definition: ssyr.f:134
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
real function slansy(NORM, UPLO, N, A, LDA, WORK)
SLANSY returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a real symmetric matrix.
Definition: slansy.f:124

Here is the call graph for this function:

Here is the caller graph for this function: