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

◆ cchkqrtp()

subroutine cchkqrtp ( real  thresh,
logical  tsterr,
integer  nm,
integer, dimension( * )  mval,
integer  nn,
integer, dimension( * )  nval,
integer  nnb,
integer, dimension( * )  nbval,
integer  nout 
)

CCHKQRTP

Purpose:
 CCHKQRTP tests CTPQRT and CTPMQRT.
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 (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 100 of file cchkqrtp.f.

102 IMPLICIT NONE
103*
104* -- LAPACK test routine --
105* -- LAPACK is a software package provided by Univ. of Tennessee, --
106* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
107*
108* .. Scalar Arguments ..
109 LOGICAL TSTERR
110 INTEGER NM, NN, NNB, NOUT
111 REAL THRESH
112* ..
113* .. Array Arguments ..
114 INTEGER MVAL( * ), NBVAL( * ), NVAL( * )
115* ..
116*
117* =====================================================================
118*
119* .. Parameters ..
120 INTEGER NTESTS
121 parameter( ntests = 6 )
122* ..
123* .. Local Scalars ..
124 CHARACTER*3 PATH
125 INTEGER I, J, K, T, L, M, N, NB, NFAIL, NERRS, NRUN,
126 $ MINMN
127* ..
128* .. Local Arrays ..
129 REAL RESULT( NTESTS )
130* ..
131* .. External Subroutines ..
132 EXTERNAL alaerh, alahd, alasum, cerrqrtp
133* ..
134* .. Scalars in Common ..
135 LOGICAL LERR, OK
136 CHARACTER*32 SRNAMT
137 INTEGER INFOT, NUNIT
138* ..
139* .. Common blocks ..
140 COMMON / infoc / infot, nunit, ok, lerr
141 COMMON / srnamc / srnamt
142* ..
143* .. Executable Statements ..
144*
145* Initialize constants
146*
147 path( 1: 1 ) = 'C'
148 path( 2: 3 ) = 'QX'
149 nrun = 0
150 nfail = 0
151 nerrs = 0
152*
153* Test the error exits
154*
155 IF( tsterr ) CALL cerrqrtp( path, nout )
156 infot = 0
157*
158* Do for each value of M
159*
160 DO i = 1, nm
161 m = mval( i )
162*
163* Do for each value of N
164*
165 DO j = 1, nn
166 n = nval( j )
167*
168* Do for each value of L
169*
170 minmn = min( m, n )
171 DO l = 0, minmn, max( minmn, 1 )
172*
173* Do for each possible value of NB
174*
175
176 DO k = 1, nnb
177 nb = nbval( k )
178*
179* Test CTPQRT and CTPMQRT
180*
181 IF( (nb.LE.n).AND.(nb.GT.0) ) THEN
182 CALL cqrt05( m, n, l, nb, result )
183*
184* Print information about the tests that did not
185* pass the threshold.
186*
187 DO t = 1, ntests
188 IF( result( t ).GE.thresh ) THEN
189 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
190 $ CALL alahd( nout, path )
191 WRITE( nout, fmt = 9999 )m, n, nb,
192 $ t, result( t )
193 nfail = nfail + 1
194 END IF
195 END DO
196 nrun = nrun + ntests
197 END IF
198 END DO
199 END DO
200 END DO
201 END DO
202*
203* Print a summary of the results.
204*
205 CALL alasum( path, nout, nfail, nrun, nerrs )
206*
207 9999 FORMAT( ' M=', i5, ', N=', i5, ', NB=', i4,
208 $ ' test(', i2, ')=', g12.5 )
209 RETURN
210*
211* End of CCHKQRTP
212*
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 cerrqrtp(path, nunit)
CERRQRTP
Definition cerrqrtp.f:55
subroutine cqrt05(m, n, l, nb, result)
CQRT05
Definition cqrt05.f:80
Here is the call graph for this function:
Here is the caller graph for this function: