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