LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cchkqrt ( real  THRESH,
logical  TSTERR,
integer  NM,
integer, dimension( * )  MVAL,
integer  NN,
integer, dimension( * )  NVAL,
integer  NNB,
integer, dimension( * )  NBVAL,
integer  NOUT 
)

CCHKQRT

Purpose:
 CCHKQRT tests CGEQRT and CGEMQRT.
Parameters
[in]THRESH
          THRESH is REAL
          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 104 of file cchkqrt.f.

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  REAL 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, m, n, nb, nfail, nerrs, nrun,
129  $ minmn
130 * ..
131 * .. Local Arrays ..
132  REAL result( ntests )
133 * ..
134 * .. External Subroutines ..
135  EXTERNAL alaerh, alahd, alasum, cerrqrt, cqrt04
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 ) = 'C'
151  path( 2: 3 ) = 'QT'
152  nrun = 0
153  nfail = 0
154  nerrs = 0
155 *
156 * Test the error exits
157 *
158  IF( tsterr ) CALL cerrqrt( path, nout )
159  infot = 0
160 *
161 * Do for each value of M in MVAL.
162 *
163  DO i = 1, nm
164  m = mval( i )
165 *
166 * Do for each value of N in NVAL.
167 *
168  DO j = 1, nn
169  n = nval( j )
170 *
171 * Do for each possible value of NB
172 *
173  minmn = min( m, n )
174  DO k = 1, nnb
175  nb = nbval( k )
176 *
177 * Test CGEQRT and CGEMQRT
178 *
179  IF( (nb.LE.minmn).AND.(nb.GT.0) ) THEN
180  CALL cqrt04( m, n, nb, result )
181 *
182 * Print information about the tests that did not
183 * pass the threshold.
184 *
185  DO t = 1, ntests
186  IF( result( t ).GE.thresh ) THEN
187  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
188  $ CALL alahd( nout, path )
189  WRITE( nout, fmt = 9999 )m, n, nb,
190  $ t, result( t )
191  nfail = nfail + 1
192  END IF
193  END DO
194  nrun = nrun + ntests
195  END IF
196  END DO
197  END DO
198  END DO
199 *
200 * Print a summary of the results.
201 *
202  CALL alasum( path, nout, nfail, nrun, nerrs )
203 *
204  9999 FORMAT( ' M=', i5, ', N=', i5, ', NB=', i4,
205  $ ' test(', i2, ')=', g12.5 )
206  RETURN
207 *
208 * End of CCHKQRT
209 *
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 cqrt04(M, N, NB, RESULT)
CQRT04
Definition: cqrt04.f:75
subroutine cerrqrt(PATH, NUNIT)
CERRQRT
Definition: cerrqrt.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: