LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
schkqrt.f
Go to the documentation of this file.
1 *> \brief \b SCHKQRT
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 SCHKQRT( THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB,
12 * NBVAL, NOUT )
13 *
14 * .. Scalar Arguments ..
15 * LOGICAL TSTERR
16 * INTEGER NM, NN, NNB, NOUT
17 * REAL THRESH
18 
19 *
20 *> \par Purpose:
21 * =============
22 *>
23 *> \verbatim
24 *>
25 *> SCHKQRT tests SGEQRT and SGEMQRT.
26 *> \endverbatim
27 *
28 * Arguments:
29 * ==========
30 *
31 *> \param[in] THRESH
32 *> \verbatim
33 *> THRESH is REAL
34 *> The threshold value for the test ratios. A result is
35 *> included in the output file if RESULT >= THRESH. To have
36 *> every test ratio printed, use THRESH = 0.
37 *> \endverbatim
38 *>
39 *> \param[in] TSTERR
40 *> \verbatim
41 *> TSTERR is LOGICAL
42 *> Flag that indicates whether error exits are to be tested.
43 *> \endverbatim
44 *>
45 *> \param[in] NM
46 *> \verbatim
47 *> NM is INTEGER
48 *> The number of values of M contained in the vector MVAL.
49 *> \endverbatim
50 *>
51 *> \param[in] MVAL
52 *> \verbatim
53 *> MVAL is INTEGER array, dimension (NM)
54 *> The values of the matrix row dimension M.
55 *> \endverbatim
56 *>
57 *> \param[in] NN
58 *> \verbatim
59 *> NN is INTEGER
60 *> The number of values of N contained in the vector NVAL.
61 *> \endverbatim
62 *>
63 *> \param[in] NVAL
64 *> \verbatim
65 *> NVAL is INTEGER array, dimension (NN)
66 *> The values of the matrix column dimension N.
67 *> \endverbatim
68 *>
69 *> \param[in] NNB
70 *> \verbatim
71 *> NNB is INTEGER
72 *> The number of values of NB contained in the vector NBVAL.
73 *> \endverbatim
74 *>
75 *> \param[in] NBVAL
76 *> \verbatim
77 *> NBVAL is INTEGER array, dimension (NBVAL)
78 *> The values of the blocksize NB.
79 *> \endverbatim
80 *>
81 *> \param[in] NOUT
82 *> \verbatim
83 *> NOUT is INTEGER
84 *> The unit number for output.
85 *> \endverbatim
86 *
87 * Authors:
88 * ========
89 *
90 *> \author Univ. of Tennessee
91 *> \author Univ. of California Berkeley
92 *> \author Univ. of Colorado Denver
93 *> \author NAG Ltd.
94 *
95 *> \date November 2011
96 *
97 *> \ingroup single_lin
98 *
99 * =====================================================================
100  SUBROUTINE schkqrt( THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB,
101  $ nbval, nout )
102  IMPLICIT NONE
103 *
104 * -- LAPACK test routine (version 3.4.0) --
105 * -- LAPACK is a software package provided by Univ. of Tennessee, --
106 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
107 * November 2011
108 *
109 * .. Scalar Arguments ..
110  LOGICAL TSTERR
111  INTEGER NM, NN, NNB, NOUT
112  REAL THRESH
113 * ..
114 * .. Array Arguments ..
115  INTEGER MVAL( * ), NBVAL( * ), NVAL( * )
116 *
117 * =====================================================================
118 *
119 * .. Parameters ..
120  INTEGER NTESTS
121  parameter ( ntests = 6 )
122 * ..
123 * .. Local Scalars ..
124  CHARACTER*3 PATH
125  INTEGER I, J, K, T, M, N, NB, NFAIL, NERRS, NRUN,
126  $ minmn
127 * ..
128 * .. Local Arrays ..
129  REAL RESULT( ntests )
130 * ..
131 * .. External Subroutines ..
132  EXTERNAL alaerh, alahd, alasum, serrqrt, sqrt04
133 * ..
134 * .. Scalars in Common ..
135  LOGICAL LERR, OK
136  CHARACTER*32 SRNAMT
137  INTEGER INFOT, NUNIT
138 * ..
139 * .. Common blocks ..
140  COMMON / infoc / infot, nunit, ok, lerr
141  COMMON / srnamc / srnamt
142 * ..
143 * .. Executable Statements ..
144 *
145 * Initialize constants
146 *
147  path( 1: 1 ) = 'S'
148  path( 2: 3 ) = 'QT'
149  nrun = 0
150  nfail = 0
151  nerrs = 0
152 *
153 * Test the error exits
154 *
155  IF( tsterr ) CALL serrqrt( path, nout )
156  infot = 0
157 *
158 * Do for each value of M in MVAL.
159 *
160  DO i = 1, nm
161  m = mval( i )
162 *
163 * Do for each value of N in NVAL.
164 *
165  DO j = 1, nn
166  n = nval( j )
167 *
168 * Do for each possible value of NB
169 *
170  minmn = min( m, n )
171  DO k = 1, nnb
172  nb = nbval( k )
173  IF( (nb.LE.minmn).AND.(nb.GT.0) ) THEN
174 *
175 * Test SGEQRT and SGEMQRT
176 *
177  CALL sqrt04( m, n, nb, result )
178 *
179 * Print information about the tests that did not
180 * pass the threshold.
181 *
182  DO t = 1, ntests
183  IF( result( t ).GE.thresh ) THEN
184  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
185  $ CALL alahd( nout, path )
186  WRITE( nout, fmt = 9999 )m, n, nb,
187  $ t, result( t )
188  nfail = nfail + 1
189  END IF
190  END DO
191  nrun = nrun + ntests
192  END IF
193  END DO
194  END DO
195  END DO
196 *
197 * Print a summary of the results.
198 *
199  CALL alasum( path, nout, nfail, nrun, nerrs )
200 *
201  9999 FORMAT( ' M=', i5, ', N=', i5, ', NB=', i4,
202  $ ' test(', i2, ')=', g12.5 )
203  RETURN
204 *
205 * End of SCHKQRT
206 *
207  END
subroutine alahd(IOUNIT, PATH)
ALAHD
Definition: alahd.f:95
subroutine alaerh(PATH, SUBNAM, INFO, INFOE, OPTS, M, N, KL, KU, N5, IMAT, NFAIL, NERRS, NOUT)
ALAERH
Definition: alaerh.f:149
subroutine sqrt04(M, N, NB, RESULT)
SQRT04
Definition: sqrt04.f:75
subroutine serrqrt(PATH, NUNIT)
SERRQRT
Definition: serrqrt.f:57
subroutine schkqrt(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
SCHKQRT
Definition: schkqrt.f:102
subroutine alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75