LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2015

Definition at line 200 of file sckgsv.f.

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