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

◆ schkqrt()

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

SCHKQRT

Purpose:
!>
!> SCHKQRT tests SGEQRT and SGEMQRT.
!> 
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 98 of file schkqrt.f.

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