LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
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 (NNB)
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*> \ingroup complex16_lin
97*
98* =====================================================================
99 SUBROUTINE zchkqrt( THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB,
100 $ NBVAL, NOUT )
101 IMPLICIT NONE
102*
103* -- LAPACK test routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 LOGICAL TSTERR
109 INTEGER NM, NN, NNB, NOUT
110 DOUBLE PRECISION THRESH
111* ..
112* .. Array Arguments ..
113 INTEGER MVAL( * ), NBVAL( * ), NVAL( * )
114* ..
115*
116* =====================================================================
117*
118* .. Parameters ..
119 INTEGER NTESTS
120 parameter( ntests = 6 )
121* ..
122* .. Local Scalars ..
123 CHARACTER*3 PATH
124 INTEGER I, J, K, T, M, N, NB, NFAIL, NERRS, NRUN,
125 $ minmn
126* ..
127* .. Local Arrays ..
128 DOUBLE PRECISION RESULT( NTESTS )
129* ..
130* .. External Subroutines ..
131 EXTERNAL alaerh, alahd, alasum, zerrqrt, zqrt04
132* ..
133* .. Scalars in Common ..
134 LOGICAL LERR, OK
135 CHARACTER*32 SRNAMT
136 INTEGER INFOT, NUNIT
137* ..
138* .. Common blocks ..
139 COMMON / infoc / infot, nunit, ok, lerr
140 COMMON / srnamc / srnamt
141* ..
142* .. Executable Statements ..
143*
144* Initialize constants
145*
146 path( 1: 1 ) = 'Z'
147 path( 2: 3 ) = 'QT'
148 nrun = 0
149 nfail = 0
150 nerrs = 0
151*
152* Test the error exits
153*
154 IF( tsterr ) CALL zerrqrt( path, nout )
155 infot = 0
156*
157* Do for each value of M in MVAL.
158*
159 DO i = 1, nm
160 m = mval( i )
161*
162* Do for each value of N in NVAL.
163*
164 DO j = 1, nn
165 n = nval( j )
166*
167* Do for each possible value of NB
168*
169 minmn = min( m, n )
170 DO k = 1, nnb
171 nb = nbval( k )
172*
173* Test ZGEQRT and ZGEMQRT
174*
175 IF( (nb.LE.minmn).AND.(nb.GT.0) ) THEN
176 CALL zqrt04( m, n, nb, result )
177*
178* Print information about the tests that did not
179* pass the threshold.
180*
181 DO t = 1, ntests
182 IF( result( t ).GE.thresh ) THEN
183 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
184 $ CALL alahd( nout, path )
185 WRITE( nout, fmt = 9999 )m, n, nb,
186 $ t, result( t )
187 nfail = nfail + 1
188 END IF
189 END DO
190 nrun = nrun + ntests
191 END IF
192 END DO
193 END DO
194 END DO
195*
196* Print a summary of the results.
197*
198 CALL alasum( path, nout, nfail, nrun, nerrs )
199*
200 9999 FORMAT( ' M=', i5, ', N=', i5, ', NB=', i4,
201 $ ' test(', i2, ')=', g12.5 )
202 RETURN
203*
204* End of ZCHKQRT
205*
206 END
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
Definition alasum.f:73
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
Definition alaerh.f:147
subroutine alahd(iounit, path)
ALAHD
Definition alahd.f:107
subroutine zchkqrt(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
ZCHKQRT
Definition zchkqrt.f:101
subroutine zerrqrt(path, nunit)
ZERRQRT
Definition zerrqrt.f:55
subroutine zqrt04(m, n, nb, result)
ZQRT04
Definition zqrt04.f:73