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

◆ sckgsv()

subroutine sckgsv ( integer nm,
integer, dimension( * ) mval,
integer, dimension( * ) pval,
integer, dimension( * ) nval,
integer nmats,
integer, dimension( 4 ) iseed,
real thresh,
integer nmax,
real, dimension( * ) a,
real, dimension( * ) af,
real, dimension( * ) b,
real, dimension( * ) bf,
real, dimension( * ) u,
real, dimension( * ) v,
real, dimension( * ) q,
real, dimension( * ) alpha,
real, dimension( * ) beta,
real, dimension( * ) r,
integer, dimension( * ) iwork,
real, dimension( * ) work,
real, dimension( * ) rwork,
integer nin,
integer nout,
integer info )

SCKGSV

Purpose:
!>
!> SCKGSV tests SGGSVD:
!>        the GSVD for M-by-N matrix A and P-by-N matrix B.
!> 
Parameters
[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]PVAL
!>          PVAL is INTEGER array, dimension (NP)
!>          The values of the matrix row dimension P.
!> 
[in]NVAL
!>          NVAL is INTEGER array, dimension (NN)
!>          The values of the matrix column dimension N.
!> 
[in]NMATS
!>          NMATS is INTEGER
!>          The number of matrix types to be tested for each combination
!>          of matrix dimensions.  If NMATS >= NTYPES (the maximum
!>          number of matrix types), then all the different types are
!>          generated for testing.  If NMATS < NTYPES, another input line
!>          is read to get the numbers of the matrix types to be used.
!> 
[in,out]ISEED
!>          ISEED is INTEGER array, dimension (4)
!>          On entry, the seed of the random number generator.  The array
!>          elements should be between 0 and 4095, otherwise they will be
!>          reduced mod 4096, and ISEED(4) must be odd.
!>          On exit, the next seed in the random number sequence after
!>          all the test matrices have been generated.
!> 
[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]NMAX
!>          NMAX is INTEGER
!>          The maximum value permitted for M or N, used in dimensioning
!>          the work arrays.
!> 
[out]A
!>          A is REAL array, dimension (NMAX*NMAX)
!> 
[out]AF
!>          AF is REAL array, dimension (NMAX*NMAX)
!> 
[out]B
!>          B is REAL array, dimension (NMAX*NMAX)
!> 
[out]BF
!>          BF is REAL array, dimension (NMAX*NMAX)
!> 
[out]U
!>          U is REAL array, dimension (NMAX*NMAX)
!> 
[out]V
!>          V is REAL array, dimension (NMAX*NMAX)
!> 
[out]Q
!>          Q is REAL array, dimension (NMAX*NMAX)
!> 
[out]ALPHA
!>          ALPHA is REAL array, dimension (NMAX)
!> 
[out]BETA
!>          BETA is REAL array, dimension (NMAX)
!> 
[out]R
!>          R is REAL array, dimension (NMAX*NMAX)
!> 
[out]IWORK
!>          IWORK is INTEGER array, dimension (NMAX)
!> 
[out]WORK
!>          WORK is REAL array, dimension (NMAX*NMAX)
!> 
[out]RWORK
!>          RWORK is REAL array, dimension (NMAX)
!> 
[in]NIN
!>          NIN is INTEGER
!>          The unit number for input.
!> 
[in]NOUT
!>          NOUT is INTEGER
!>          The unit number for output.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0 :  successful exit
!>          > 0 :  If SLATMS returns an error code, the absolute value
!>                 of it is returned.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 195 of file sckgsv.f.

198*
199* -- LAPACK test routine --
200* -- LAPACK is a software package provided by Univ. of Tennessee, --
201* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
202*
203* .. Scalar Arguments ..
204 INTEGER INFO, NIN, NM, NMATS, NMAX, NOUT
205 REAL THRESH
206* ..
207* .. Array Arguments ..
208 INTEGER ISEED( 4 ), IWORK( * ), MVAL( * ), NVAL( * ),
209 $ PVAL( * )
210 REAL A( * ), AF( * ), ALPHA( * ), B( * ), BETA( * ),
211 $ BF( * ), Q( * ), R( * ), RWORK( * ), U( * ),
212 $ V( * ), WORK( * )
213* ..
214*
215* =====================================================================
216*
217* .. Parameters ..
218 INTEGER NTESTS
219 parameter( ntests = 12 )
220 INTEGER NTYPES
221 parameter( ntypes = 8 )
222* ..
223* .. Local Scalars ..
224 LOGICAL FIRSTT
225 CHARACTER DISTA, DISTB, TYPE
226 CHARACTER*3 PATH
227 INTEGER I, IINFO, IM, IMAT, KLA, KLB, KUA, KUB, LDA,
228 $ LDB, LDQ, LDR, LDU, LDV, LWORK, M, MODEA,
229 $ MODEB, N, NFAIL, NRUN, NT, P
230 REAL ANORM, BNORM, CNDNMA, CNDNMB
231* ..
232* .. Local Arrays ..
233 LOGICAL DOTYPE( NTYPES )
234 REAL RESULT( NTESTS )
235* ..
236* .. External Subroutines ..
238* ..
239* .. Intrinsic Functions ..
240 INTRINSIC abs
241* ..
242* .. Executable Statements ..
243*
244* Initialize constants and the random number seed.
245*
246 path( 1: 3 ) = 'GSV'
247 info = 0
248 nrun = 0
249 nfail = 0
250 firstt = .true.
251 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
252 lda = nmax
253 ldb = nmax
254 ldu = nmax
255 ldv = nmax
256 ldq = nmax
257 ldr = nmax
258 lwork = nmax*nmax
259*
260* Do for each value of M in MVAL.
261*
262 DO 30 im = 1, nm
263 m = mval( im )
264 p = pval( im )
265 n = nval( im )
266*
267 DO 20 imat = 1, ntypes
268*
269* Do the tests only if DOTYPE( IMAT ) is true.
270*
271 IF( .NOT.dotype( imat ) )
272 $ GO TO 20
273*
274* Set up parameters with SLATB9 and generate test
275* matrices A and B with SLATMS.
276*
277 CALL slatb9( path, imat, m, p, n, TYPE, KLA, KUA, KLB, KUB,
278 $ ANORM, BNORM, MODEA, MODEB, CNDNMA, CNDNMB,
279 $ DISTA, DISTB )
280*
281* Generate M by N matrix A
282*
283 CALL slatms( m, n, dista, iseed, TYPE, RWORK, MODEA, CNDNMA,
284 $ ANORM, KLA, KUA, 'No packing', A, LDA, WORK,
285 $ IINFO )
286 IF( iinfo.NE.0 ) THEN
287 WRITE( nout, fmt = 9999 )iinfo
288 info = abs( iinfo )
289 GO TO 20
290 END IF
291*
292 CALL slatms( p, n, distb, iseed, TYPE, RWORK, MODEB, CNDNMB,
293 $ BNORM, KLB, KUB, 'No packing', B, LDB, WORK,
294 $ IINFO )
295 IF( iinfo.NE.0 ) THEN
296 WRITE( nout, fmt = 9999 )iinfo
297 info = abs( iinfo )
298 GO TO 20
299 END IF
300*
301 nt = 6
302*
303 CALL sgsvts3( m, p, n, a, af, lda, b, bf, ldb, u, ldu, v,
304 $ ldv, q, ldq, alpha, beta, r, ldr, iwork, work,
305 $ lwork, rwork, result )
306*
307* Print information about the tests that did not
308* pass the threshold.
309*
310 DO 10 i = 1, nt
311 IF( result( i ).GE.thresh ) THEN
312 IF( nfail.EQ.0 .AND. firstt ) THEN
313 firstt = .false.
314 CALL alahdg( nout, path )
315 END IF
316 WRITE( nout, fmt = 9998 )m, p, n, imat, i,
317 $ result( i )
318 nfail = nfail + 1
319 END IF
320 10 CONTINUE
321 nrun = nrun + nt
322 20 CONTINUE
323 30 CONTINUE
324*
325* Print a summary of the results.
326*
327 CALL alasum( path, nout, nfail, nrun, 0 )
328*
329 9999 FORMAT( ' SLATMS in SCKGSV INFO = ', i5 )
330 9998 FORMAT( ' M=', i4, ' P=', i4, ', N=', i4, ', type ', i2,
331 $ ', test ', i2, ', ratio=', g13.6 )
332 RETURN
333*
334* End of SCKGSV
335*
subroutine alareq(path, nmats, dotype, ntypes, nin, nout)
ALAREQ
Definition alareq.f:90
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
Definition alasum.f:73
subroutine alahdg(iounit, path)
ALAHDG
Definition alahdg.f:62
subroutine sgsvts3(m, p, n, a, af, lda, b, bf, ldb, u, ldu, v, ldv, q, ldq, alpha, beta, r, ldr, iwork, work, lwork, rwork, result)
SGSVTS3
Definition sgsvts3.f:210
subroutine slatb9(path, imat, m, p, n, type, kla, kua, klb, kub, anorm, bnorm, modea, modeb, cndnma, cndnmb, dista, distb)
SLATB9
Definition slatb9.f:170
subroutine slatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
SLATMS
Definition slatms.f:321
Here is the call graph for this function:
Here is the caller graph for this function: