LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 (NBVAL)
          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.
Date
November 2011

Definition at line 103 of file zchkqrt.f.

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 *
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 alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75

Here is the call graph for this function:

Here is the caller graph for this function: