LAPACK  3.9.0
LAPACK: Linear Algebra PACKage
zchkunhr_col.f
Go to the documentation of this file.
1 *> \brief \b ZCHKUNHR_COL
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 ZCHKUNHR_COL( 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 *> ZCHKUNHR_COL tests ZUNHR_COL using ZLATSQR and ZGEMQRT. Therefore, ZLATSQR
28 *> (used in ZGEQR) and ZGEMQRT (used in ZGEMQR) have to be tested
29 *> before this test.
30 *>
31 *> \endverbatim
32 *
33 * Arguments:
34 * ==========
35 *
36 *> \param[in] THRESH
37 *> \verbatim
38 *> THRESH is DOUBLE PRECISION
39 *> The threshold value for the test ratios. A result is
40 *> included in the output file if RESULT >= THRESH. To have
41 *> every test ratio printed, use THRESH = 0.
42 *> \endverbatim
43 *>
44 *> \param[in] TSTERR
45 *> \verbatim
46 *> TSTERR is LOGICAL
47 *> Flag that indicates whether error exits are to be tested.
48 *> \endverbatim
49 *>
50 *> \param[in] NM
51 *> \verbatim
52 *> NM is INTEGER
53 *> The number of values of M contained in the vector MVAL.
54 *> \endverbatim
55 *>
56 *> \param[in] MVAL
57 *> \verbatim
58 *> MVAL is INTEGER array, dimension (NM)
59 *> The values of the matrix row dimension M.
60 *> \endverbatim
61 *>
62 *> \param[in] NN
63 *> \verbatim
64 *> NN is INTEGER
65 *> The number of values of N contained in the vector NVAL.
66 *> \endverbatim
67 *>
68 *> \param[in] NVAL
69 *> \verbatim
70 *> NVAL is INTEGER array, dimension (NN)
71 *> The values of the matrix column dimension N.
72 *> \endverbatim
73 *>
74 *> \param[in] NNB
75 *> \verbatim
76 *> NNB is INTEGER
77 *> The number of values of NB contained in the vector NBVAL.
78 *> \endverbatim
79 *>
80 *> \param[in] NBVAL
81 *> \verbatim
82 *> NBVAL is INTEGER array, dimension (NBVAL)
83 *> The values of the blocksize NB.
84 *> \endverbatim
85 *>
86 *> \param[in] NOUT
87 *> \verbatim
88 *> NOUT is INTEGER
89 *> The unit number for output.
90 *> \endverbatim
91 *
92 * Authors:
93 * ========
94 *
95 *> \author Univ. of Tennessee
96 *> \author Univ. of California Berkeley
97 *> \author Univ. of Colorado Denver
98 *> \author NAG Ltd.
99 *
100 *> \date November 2019
101 *
102 *> \ingroup complex16_lin
103 *
104 * =====================================================================
105  SUBROUTINE zchkunhr_col( THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB,
106  $ NBVAL, NOUT )
107  IMPLICIT NONE
108 *
109 * -- LAPACK test routine (version 3.7.0) --
110 * -- LAPACK is a software package provided by Univ. of Tennessee, --
111 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
112 * December 2016
113 *
114 * .. Scalar Arguments ..
115  LOGICAL TSTERR
116  INTEGER NM, NN, NNB, NOUT
117  DOUBLE PRECISION THRESH
118 * ..
119 * .. Array Arguments ..
120  INTEGER MVAL( * ), NBVAL( * ), NVAL( * )
121 * ..
122 *
123 * =====================================================================
124 *
125 * .. Parameters ..
126  INTEGER NTESTS
127  parameter( ntests = 6 )
128 * ..
129 * .. Local Scalars ..
130  CHARACTER(LEN=3) PATH
131  INTEGER I, IMB1, INB1, INB2, J, T, M, N, MB1, NB1,
132  $ nb2, nfail, nerrs, nrun
133 *
134 * .. Local Arrays ..
135  DOUBLE PRECISION RESULT( NTESTS )
136 * ..
137 * .. External Subroutines ..
139 * ..
140 * .. Intrinsic Functions ..
141  INTRINSIC max, min
142 * ..
143 * .. Scalars in Common ..
144  LOGICAL LERR, OK
145  CHARACTER(LEN=32) SRNAMT
146  INTEGER INFOT, NUNIT
147 * ..
148 * .. Common blocks ..
149  COMMON / infoc / infot, nunit, ok, lerr
150  COMMON / srnamc / srnamt
151 * ..
152 * .. Executable Statements ..
153 *
154 * Initialize constants
155 *
156  path( 1: 1 ) = 'Z'
157  path( 2: 3 ) = 'HH'
158  nrun = 0
159  nfail = 0
160  nerrs = 0
161 *
162 * Test the error exits
163 *
164  IF( tsterr ) CALL zerrunhr_col( path, nout )
165  infot = 0
166 *
167 * Do for each value of M in MVAL.
168 *
169  DO i = 1, nm
170  m = mval( i )
171 *
172 * Do for each value of N in NVAL.
173 *
174  DO j = 1, nn
175  n = nval( j )
176 *
177 * Only for M >= N
178 *
179  IF ( min( m, n ).GT.0 .AND. m.GE.n ) THEN
180 *
181 * Do for each possible value of MB1
182 *
183  DO imb1 = 1, nnb
184  mb1 = nbval( imb1 )
185 *
186 * Only for MB1 > N
187 *
188  IF ( mb1.GT.n ) THEN
189 *
190 * Do for each possible value of NB1
191 *
192  DO inb1 = 1, nnb
193  nb1 = nbval( inb1 )
194 *
195 * Do for each possible value of NB2
196 *
197  DO inb2 = 1, nnb
198  nb2 = nbval( inb2 )
199 *
200  IF( nb1.GT.0 .AND. nb2.GT.0 ) THEN
201 *
202 * Test ZUNHR_COL
203 *
204  CALL zunhr_col01( m, n, mb1, nb1, nb2,
205  $ result )
206 *
207 * Print information about the tests that did
208 * not pass the threshold.
209 *
210  DO t = 1, ntests
211  IF( result( t ).GE.thresh ) THEN
212  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
213  $ CALL alahd( nout, path )
214  WRITE( nout, fmt = 9999 ) m, n, mb1,
215  $ nb1, nb2, t, result( t )
216  nfail = nfail + 1
217  END IF
218  END DO
219  nrun = nrun + ntests
220  END IF
221  END DO
222  END DO
223  END IF
224  END DO
225  END IF
226  END DO
227  END DO
228 *
229 * Print a summary of the results.
230 *
231  CALL alasum( path, nout, nfail, nrun, nerrs )
232 *
233  9999 FORMAT( 'M=', i5, ', N=', i5, ', MB1=', i5,
234  $ ', NB1=', i5, ', NB2=', i5,' test(', i2, ')=', g12.5 )
235  RETURN
236 *
237 * End of ZCHKUNHR_COL
238 *
239  END
zerrunhr_col
subroutine zerrunhr_col(PATH, NUNIT)
ZERRUNHR_COL
Definition: zerrunhr_col.f:58
zchkunhr_col
subroutine zchkunhr_col(THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB, NBVAL, NOUT)
ZCHKUNHR_COL
Definition: zchkunhr_col.f:107
alahd
subroutine alahd(IOUNIT, PATH)
ALAHD
Definition: alahd.f:109
zunhr_col01
subroutine zunhr_col01(M, N, MB1, NB1, NB2, RESULT)
ZUNHR_COL01
Definition: zunhr_col01.f:89
alasum
subroutine alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75