LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ddrvrf1.f
Go to the documentation of this file.
1 *> \brief \b DDRVRF1
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 DDRVRF1( NOUT, NN, NVAL, THRESH, A, LDA, ARF, WORK )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER LDA, NN, NOUT
15 * DOUBLE PRECISION THRESH
16 * ..
17 * .. Array Arguments ..
18 * INTEGER NVAL( NN )
19 * DOUBLE PRECISION A( LDA, * ), ARF( * ), WORK( * )
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> DDRVRF1 tests the LAPACK RFP routines:
29 *> DLANSF
30 *> \endverbatim
31 *
32 * Arguments:
33 * ==========
34 *
35 *> \param[in] NOUT
36 *> \verbatim
37 *> NOUT is INTEGER
38 *> The unit number for output.
39 *> \endverbatim
40 *>
41 *> \param[in] NN
42 *> \verbatim
43 *> NN is INTEGER
44 *> The number of values of N contained in the vector NVAL.
45 *> \endverbatim
46 *>
47 *> \param[in] NVAL
48 *> \verbatim
49 *> NVAL is INTEGER array, dimension (NN)
50 *> The values of the matrix dimension N.
51 *> \endverbatim
52 *>
53 *> \param[in] THRESH
54 *> \verbatim
55 *> THRESH is DOUBLE PRECISION
56 *> The threshold value for the test ratios. A result is
57 *> included in the output file if RESULT >= THRESH. To have
58 *> every test ratio printed, use THRESH = 0.
59 *> \endverbatim
60 *>
61 *> \param[out] A
62 *> \verbatim
63 *> A is DOUBLE PRECISION array, dimension (LDA,NMAX)
64 *> \endverbatim
65 *>
66 *> \param[in] LDA
67 *> \verbatim
68 *> LDA is INTEGER
69 *> The leading dimension of the array A. LDA >= max(1,NMAX).
70 *> \endverbatim
71 *>
72 *> \param[out] ARF
73 *> \verbatim
74 *> ARF is DOUBLE PRECISION array, dimension ((NMAX*(NMAX+1))/2).
75 *> \endverbatim
76 *>
77 *> \param[out] WORK
78 *> \verbatim
79 *> WORK is DOUBLE PRECISION array, dimension ( NMAX )
80 *> \endverbatim
81 *
82 * Authors:
83 * ========
84 *
85 *> \author Univ. of Tennessee
86 *> \author Univ. of California Berkeley
87 *> \author Univ. of Colorado Denver
88 *> \author NAG Ltd.
89 *
90 *> \date November 2011
91 *
92 *> \ingroup double_lin
93 *
94 * =====================================================================
95  SUBROUTINE ddrvrf1( NOUT, NN, NVAL, THRESH, A, LDA, ARF, WORK )
96 *
97 * -- LAPACK test routine (version 3.4.0) --
98 * -- LAPACK is a software package provided by Univ. of Tennessee, --
99 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
100 * November 2011
101 *
102 * .. Scalar Arguments ..
103  INTEGER lda, nn, nout
104  DOUBLE PRECISION thresh
105 * ..
106 * .. Array Arguments ..
107  INTEGER nval( nn )
108  DOUBLE PRECISION a( lda, * ), arf( * ), work( * )
109 * ..
110 *
111 * =====================================================================
112 * ..
113 * .. Parameters ..
114  DOUBLE PRECISION one
115  parameter( one = 1.0d+0 )
116  INTEGER ntests
117  parameter( ntests = 1 )
118 * ..
119 * .. Local Scalars ..
120  CHARACTER uplo, cform, norm
121  INTEGER i, iform, iin, iit, info, inorm, iuplo, j, n,
122  + nerrs, nfail, nrun
123  DOUBLE PRECISION eps, large, norma, normarf, small
124 * ..
125 * .. Local Arrays ..
126  CHARACTER uplos( 2 ), forms( 2 ), norms( 4 )
127  INTEGER iseed( 4 ), iseedy( 4 )
128  DOUBLE PRECISION result( ntests )
129 * ..
130 * .. External Functions ..
131  DOUBLE PRECISION dlamch, dlansy, dlansf, dlarnd
132  EXTERNAL dlamch, dlansy, dlansf, dlarnd
133 * ..
134 * .. External Subroutines ..
135  EXTERNAL dtrttf
136 * ..
137 * .. Scalars in Common ..
138  CHARACTER*32 srnamt
139 * ..
140 * .. Common blocks ..
141  common / srnamc / srnamt
142 * ..
143 * .. Data statements ..
144  DATA iseedy / 1988, 1989, 1990, 1991 /
145  DATA uplos / 'U', 'L' /
146  DATA forms / 'N', 'T' /
147  DATA norms / 'M', '1', 'I', 'F' /
148 * ..
149 * .. Executable Statements ..
150 *
151 * Initialize constants and the random number seed.
152 *
153  nrun = 0
154  nfail = 0
155  nerrs = 0
156  info = 0
157  DO 10 i = 1, 4
158  iseed( i ) = iseedy( i )
159  10 continue
160 *
161  eps = dlamch( 'Precision' )
162  small = dlamch( 'Safe minimum' )
163  large = one / small
164  small = small * lda * lda
165  large = large / lda / lda
166 *
167  DO 130 iin = 1, nn
168 *
169  n = nval( iin )
170 *
171  DO 120 iit = 1, 3
172 * Nothing to do for N=0
173  IF ( n .EQ. 0 ) exit
174 *
175 * IIT = 1 : random matrix
176 * IIT = 2 : random matrix scaled near underflow
177 * IIT = 3 : random matrix scaled near overflow
178 *
179  DO j = 1, n
180  DO i = 1, n
181  a( i, j) = dlarnd( 2, iseed )
182  END DO
183  END DO
184 *
185  IF ( iit.EQ.2 ) THEN
186  DO j = 1, n
187  DO i = 1, n
188  a( i, j) = a( i, j ) * large
189  END DO
190  END DO
191  END IF
192 *
193  IF ( iit.EQ.3 ) THEN
194  DO j = 1, n
195  DO i = 1, n
196  a( i, j) = a( i, j) * small
197  END DO
198  END DO
199  END IF
200 *
201 * Do first for UPLO = 'U', then for UPLO = 'L'
202 *
203  DO 110 iuplo = 1, 2
204 *
205  uplo = uplos( iuplo )
206 *
207 * Do first for CFORM = 'N', then for CFORM = 'C'
208 *
209  DO 100 iform = 1, 2
210 *
211  cform = forms( iform )
212 *
213  srnamt = 'DTRTTF'
214  CALL dtrttf( cform, uplo, n, a, lda, arf, info )
215 *
216 * Check error code from DTRTTF
217 *
218  IF( info.NE.0 ) THEN
219  IF( nfail.EQ.0 .AND. nerrs.EQ.0 ) THEN
220  WRITE( nout, * )
221  WRITE( nout, fmt = 9999 )
222  END IF
223  WRITE( nout, fmt = 9998 ) srnamt, uplo, cform, n
224  nerrs = nerrs + 1
225  go to 100
226  END IF
227 *
228  DO 90 inorm = 1, 4
229 *
230 * Check all four norms: 'M', '1', 'I', 'F'
231 *
232  norm = norms( inorm )
233  normarf = dlansf( norm, cform, uplo, n, arf, work )
234  norma = dlansy( norm, uplo, n, a, lda, work )
235 *
236  result(1) = ( norma - normarf ) / norma / eps
237  nrun = nrun + 1
238 *
239  IF( result(1).GE.thresh ) THEN
240  IF( nfail.EQ.0 .AND. nerrs.EQ.0 ) THEN
241  WRITE( nout, * )
242  WRITE( nout, fmt = 9999 )
243  END IF
244  WRITE( nout, fmt = 9997 ) 'DLANSF',
245  + n, iit, uplo, cform, norm, result(1)
246  nfail = nfail + 1
247  END IF
248  90 continue
249  100 continue
250  110 continue
251  120 continue
252  130 continue
253 *
254 * Print a summary of the results.
255 *
256  IF ( nfail.EQ.0 ) THEN
257  WRITE( nout, fmt = 9996 ) 'DLANSF', nrun
258  ELSE
259  WRITE( nout, fmt = 9995 ) 'DLANSF', nfail, nrun
260  END IF
261  IF ( nerrs.NE.0 ) THEN
262  WRITE( nout, fmt = 9994 ) nerrs, 'DLANSF'
263  END IF
264 *
265  9999 format( 1x,
266 ' *** Error(s) or Failure(s) while testing DLANSF + ***')
267  9998 format( 1x, ' Error in ',a6,' with UPLO=''',a1,''', FORM=''',
268  + a1,''', N=',i5)
269  9997 format( 1x, ' Failure in ',a6,' N=',i5,' TYPE=',i5,' UPLO=''',
270  + a1, ''', FORM =''',a1,''', NORM=''',a1,''', test=',g12.5)
271  9996 format( 1x, 'All tests for ',a6,' auxiliary routine passed the ',
272  + 'threshold ( ',i5,' tests run)')
273  9995 format( 1x, a6, ' auxiliary routine: ',i5,' out of ',i5,
274  + ' tests failed to pass the threshold')
275  9994 format( 26x, i5,' error message recorded (',a6,')')
276 *
277  return
278 *
279 * End of DDRVRF1
280 *
281  END