LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
sget51.f
Go to the documentation of this file.
1 *> \brief \b SGET51
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 SGET51( ITYPE, N, A, LDA, B, LDB, U, LDU, V, LDV, WORK,
12 * RESULT )
13 *
14 * .. Scalar Arguments ..
15 * INTEGER ITYPE, LDA, LDB, LDU, LDV, N
16 * REAL RESULT
17 * ..
18 * .. Array Arguments ..
19 * REAL A( LDA, * ), B( LDB, * ), U( LDU, * ),
20 * $ V( LDV, * ), WORK( * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> SGET51 generally checks a decomposition of the form
30 *>
31 *> A = U B V'
32 *>
33 *> where ' means transpose and U and V are orthogonal.
34 *>
35 *> Specifically, if ITYPE=1
36 *>
37 *> RESULT = | A - U B V' | / ( |A| n ulp )
38 *>
39 *> If ITYPE=2, then:
40 *>
41 *> RESULT = | A - B | / ( |A| n ulp )
42 *>
43 *> If ITYPE=3, then:
44 *>
45 *> RESULT = | I - UU' | / ( n ulp )
46 *> \endverbatim
47 *
48 * Arguments:
49 * ==========
50 *
51 *> \param[in] ITYPE
52 *> \verbatim
53 *> ITYPE is INTEGER
54 *> Specifies the type of tests to be performed.
55 *> =1: RESULT = | A - U B V' | / ( |A| n ulp )
56 *> =2: RESULT = | A - B | / ( |A| n ulp )
57 *> =3: RESULT = | I - UU' | / ( n ulp )
58 *> \endverbatim
59 *>
60 *> \param[in] N
61 *> \verbatim
62 *> N is INTEGER
63 *> The size of the matrix. If it is zero, SGET51 does nothing.
64 *> It must be at least zero.
65 *> \endverbatim
66 *>
67 *> \param[in] A
68 *> \verbatim
69 *> A is REAL array, dimension (LDA, N)
70 *> The original (unfactored) matrix.
71 *> \endverbatim
72 *>
73 *> \param[in] LDA
74 *> \verbatim
75 *> LDA is INTEGER
76 *> The leading dimension of A. It must be at least 1
77 *> and at least N.
78 *> \endverbatim
79 *>
80 *> \param[in] B
81 *> \verbatim
82 *> B is REAL array, dimension (LDB, N)
83 *> The factored matrix.
84 *> \endverbatim
85 *>
86 *> \param[in] LDB
87 *> \verbatim
88 *> LDB is INTEGER
89 *> The leading dimension of B. It must be at least 1
90 *> and at least N.
91 *> \endverbatim
92 *>
93 *> \param[in] U
94 *> \verbatim
95 *> U is REAL array, dimension (LDU, N)
96 *> The orthogonal matrix on the left-hand side in the
97 *> decomposition.
98 *> Not referenced if ITYPE=2
99 *> \endverbatim
100 *>
101 *> \param[in] LDU
102 *> \verbatim
103 *> LDU is INTEGER
104 *> The leading dimension of U. LDU must be at least N and
105 *> at least 1.
106 *> \endverbatim
107 *>
108 *> \param[in] V
109 *> \verbatim
110 *> V is REAL array, dimension (LDV, N)
111 *> The orthogonal matrix on the left-hand side in the
112 *> decomposition.
113 *> Not referenced if ITYPE=2
114 *> \endverbatim
115 *>
116 *> \param[in] LDV
117 *> \verbatim
118 *> LDV is INTEGER
119 *> The leading dimension of V. LDV must be at least N and
120 *> at least 1.
121 *> \endverbatim
122 *>
123 *> \param[out] WORK
124 *> \verbatim
125 *> WORK is REAL array, dimension (2*N**2)
126 *> \endverbatim
127 *>
128 *> \param[out] RESULT
129 *> \verbatim
130 *> RESULT is REAL
131 *> The values computed by the test specified by ITYPE. The
132 *> value is currently limited to 1/ulp, to avoid overflow.
133 *> Errors are flagged by RESULT=10/ulp.
134 *> \endverbatim
135 *
136 * Authors:
137 * ========
138 *
139 *> \author Univ. of Tennessee
140 *> \author Univ. of California Berkeley
141 *> \author Univ. of Colorado Denver
142 *> \author NAG Ltd.
143 *
144 *> \date November 2011
145 *
146 *> \ingroup single_eig
147 *
148 * =====================================================================
149  SUBROUTINE sget51( ITYPE, N, A, LDA, B, LDB, U, LDU, V, LDV, WORK,
150  $ result )
151 *
152 * -- LAPACK test routine (version 3.4.0) --
153 * -- LAPACK is a software package provided by Univ. of Tennessee, --
154 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155 * November 2011
156 *
157 * .. Scalar Arguments ..
158  INTEGER ITYPE, LDA, LDB, LDU, LDV, N
159  REAL RESULT
160 * ..
161 * .. Array Arguments ..
162  REAL A( lda, * ), B( ldb, * ), U( ldu, * ),
163  $ v( ldv, * ), work( * )
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Parameters ..
169  REAL ZERO, ONE, TEN
170  parameter ( zero = 0.0, one = 1.0e0, ten = 10.0e0 )
171 * ..
172 * .. Local Scalars ..
173  INTEGER JCOL, JDIAG, JROW
174  REAL ANORM, ULP, UNFL, WNORM
175 * ..
176 * .. External Functions ..
177  REAL SLAMCH, SLANGE
178  EXTERNAL slamch, slange
179 * ..
180 * .. External Subroutines ..
181  EXTERNAL sgemm, slacpy
182 * ..
183 * .. Intrinsic Functions ..
184  INTRINSIC max, min, real
185 * ..
186 * .. Executable Statements ..
187 *
188  result = zero
189  IF( n.LE.0 )
190  $ RETURN
191 *
192 * Constants
193 *
194  unfl = slamch( 'Safe minimum' )
195  ulp = slamch( 'Epsilon' )*slamch( 'Base' )
196 *
197 * Some Error Checks
198 *
199  IF( itype.LT.1 .OR. itype.GT.3 ) THEN
200  result = ten / ulp
201  RETURN
202  END IF
203 *
204  IF( itype.LE.2 ) THEN
205 *
206 * Tests scaled by the norm(A)
207 *
208  anorm = max( slange( '1', n, n, a, lda, work ), unfl )
209 *
210  IF( itype.EQ.1 ) THEN
211 *
212 * ITYPE=1: Compute W = A - UBV'
213 *
214  CALL slacpy( ' ', n, n, a, lda, work, n )
215  CALL sgemm( 'N', 'N', n, n, n, one, u, ldu, b, ldb, zero,
216  $ work( n**2+1 ), n )
217 *
218  CALL sgemm( 'N', 'C', n, n, n, -one, work( n**2+1 ), n, v,
219  $ ldv, one, work, n )
220 *
221  ELSE
222 *
223 * ITYPE=2: Compute W = A - B
224 *
225  CALL slacpy( ' ', n, n, b, ldb, work, n )
226 *
227  DO 20 jcol = 1, n
228  DO 10 jrow = 1, n
229  work( jrow+n*( jcol-1 ) ) = work( jrow+n*( jcol-1 ) )
230  $ - a( jrow, jcol )
231  10 CONTINUE
232  20 CONTINUE
233  END IF
234 *
235 * Compute norm(W)/ ( ulp*norm(A) )
236 *
237  wnorm = slange( '1', n, n, work, n, work( n**2+1 ) )
238 *
239  IF( anorm.GT.wnorm ) THEN
240  result = ( wnorm / anorm ) / ( n*ulp )
241  ELSE
242  IF( anorm.LT.one ) THEN
243  result = ( min( wnorm, n*anorm ) / anorm ) / ( n*ulp )
244  ELSE
245  result = min( wnorm / anorm, REAL( N ) ) / ( N*ULP )
246  END IF
247  END IF
248 *
249  ELSE
250 *
251 * Tests not scaled by norm(A)
252 *
253 * ITYPE=3: Compute UU' - I
254 *
255  CALL sgemm( 'N', 'C', n, n, n, one, u, ldu, u, ldu, zero, work,
256  $ n )
257 *
258  DO 30 jdiag = 1, n
259  work( ( n+1 )*( jdiag-1 )+1 ) = work( ( n+1 )*( jdiag-1 )+
260  $ 1 ) - one
261  30 CONTINUE
262 *
263  result = min( slange( '1', n, n, work, n, work( n**2+1 ) ),
264  $ REAL( N ) ) / ( N*ULP )
265  END IF
266 *
267  RETURN
268 *
269 * End of SGET51
270 *
271  END
subroutine sgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
SGEMM
Definition: sgemm.f:189
subroutine slacpy(UPLO, M, N, A, LDA, B, LDB)
SLACPY copies all or part of one two-dimensional array to another.
Definition: slacpy.f:105
subroutine sget51(ITYPE, N, A, LDA, B, LDB, U, LDU, V, LDV, WORK, RESULT)
SGET51
Definition: sget51.f:151