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