LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zchkqrt()

subroutine zchkqrt ( double precision  thresh,
logical  tsterr,
integer  nm,
integer, dimension( * )  mval,
integer  nn,
integer, dimension( * )  nval,
integer  nnb,
integer, dimension( * )  nbval,
integer  nout 
)

ZCHKQRT

Purpose:
 ZCHKQRT tests ZGEQRT and ZGEMQRT.
Parameters
[in]THRESH
          THRESH is DOUBLE PRECISION
          The threshold value for the test ratios.  A result is
          included in the output file if RESULT >= THRESH.  To have
          every test ratio printed, use THRESH = 0.
[in]TSTERR
          TSTERR is LOGICAL
          Flag that indicates whether error exits are to be tested.
[in]NM
          NM is INTEGER
          The number of values of M contained in the vector MVAL.
[in]MVAL
          MVAL is INTEGER array, dimension (NM)
          The values of the matrix row dimension M.
[in]NN
          NN is INTEGER
          The number of values of N contained in the vector NVAL.
[in]NVAL
          NVAL is INTEGER array, dimension (NN)
          The values of the matrix column dimension N.
[in]NNB
          NNB is INTEGER
          The number of values of NB contained in the vector NBVAL.
[in]NBVAL
          NBVAL is INTEGER array, dimension (NNB)
          The values of the blocksize NB.
[in]NOUT
          NOUT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 99 of file zchkqrt.f.

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*
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 zerrqrt(path, nunit)
ZERRQRT
Definition zerrqrt.f:55
subroutine zqrt04(m, n, nb, result)
ZQRT04
Definition zqrt04.f:73
Here is the call graph for this function:
Here is the caller graph for this function: