LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cckgqr ( integer  NM,
integer, dimension( * )  MVAL,
integer  NP,
integer, dimension( * )  PVAL,
integer  NN,
integer, dimension( * )  NVAL,
integer  NMATS,
integer, dimension( 4 )  ISEED,
real  THRESH,
integer  NMAX,
complex, dimension( * )  A,
complex, dimension( * )  AF,
complex, dimension( * )  AQ,
complex, dimension( * )  AR,
complex, dimension( * )  TAUA,
complex, dimension( * )  B,
complex, dimension( * )  BF,
complex, dimension( * )  BZ,
complex, dimension( * )  BT,
complex, dimension( * )  BWK,
complex, dimension( * )  TAUB,
complex, dimension( * )  WORK,
real, dimension( * )  RWORK,
integer  NIN,
integer  NOUT,
integer  INFO 
)

CCKGQR

Purpose:
 CCKGQR tests
 CGGQRF: GQR factorization for N-by-M matrix A and N-by-P matrix B,
 CGGRQF: GRQ factorization 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(column) dimension M.
[in]NP
          NP is INTEGER
          The number of values of P contained in the vector PVAL.
[in]PVAL
          PVAL is INTEGER array, dimension (NP)
          The values of the matrix row(column) dimension P.
[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(row) 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 COMPLEX array, dimension (NMAX*NMAX)
[out]AF
          AF is COMPLEX array, dimension (NMAX*NMAX)
[out]AQ
          AQ is COMPLEX array, dimension (NMAX*NMAX)
[out]AR
          AR is COMPLEX array, dimension (NMAX*NMAX)
[out]TAUA
          TAUA is COMPLEX array, dimension (NMAX)
[out]B
          B is COMPLEX array, dimension (NMAX*NMAX)
[out]BF
          BF is COMPLEX array, dimension (NMAX*NMAX)
[out]BZ
          BZ is COMPLEX array, dimension (NMAX*NMAX)
[out]BT
          BT is COMPLEX array, dimension (NMAX*NMAX)
[out]BWK
          BWK is COMPLEX array, dimension (NMAX*NMAX)
[out]TAUB
          TAUB is COMPLEX array, dimension (NMAX)
[out]WORK
          WORK is COMPLEX 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 CLATMS 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 2011

Definition at line 213 of file cckgqr.f.

213 *
214 * -- LAPACK test routine (version 3.4.0) --
215 * -- LAPACK is a software package provided by Univ. of Tennessee, --
216 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
217 * November 2011
218 *
219 * .. Scalar Arguments ..
220  INTEGER info, nin, nm, nmats, nmax, nn, nout, np
221  REAL thresh
222 * ..
223 * .. Array Arguments ..
224  INTEGER iseed( 4 ), mval( * ), nval( * ), pval( * )
225  REAL rwork( * )
226  COMPLEX a( * ), af( * ), aq( * ), ar( * ), b( * ),
227  $ bf( * ), bt( * ), bwk( * ), bz( * ), taua( * ),
228  $ taub( * ), work( * )
229 * ..
230 *
231 * =====================================================================
232 *
233 * .. Parameters ..
234  INTEGER ntests
235  parameter ( ntests = 7 )
236  INTEGER ntypes
237  parameter ( ntypes = 8 )
238 * ..
239 * .. Local Scalars ..
240  LOGICAL firstt
241  CHARACTER dista, distb, type
242  CHARACTER*3 path
243  INTEGER i, iinfo, im, imat, in, ip, kla, klb, kua, kub,
244  $ lda, ldb, lwork, m, modea, modeb, n, nfail,
245  $ nrun, nt, p
246  REAL anorm, bnorm, cndnma, cndnmb
247 * ..
248 * .. Local Arrays ..
249  LOGICAL dotype( ntypes )
250  REAL result( ntests )
251 * ..
252 * .. External Subroutines ..
253  EXTERNAL alahdg, alareq, alasum, cgqrts, cgrqts, clatms,
254  $ slatb9
255 * ..
256 * .. Intrinsic Functions ..
257  INTRINSIC abs
258 * ..
259 * .. Executable Statements ..
260 *
261 * Initialize constants.
262 *
263  path( 1: 3 ) = 'GQR'
264  info = 0
265  nrun = 0
266  nfail = 0
267  firstt = .true.
268  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
269  lda = nmax
270  ldb = nmax
271  lwork = nmax*nmax
272 *
273 * Do for each value of M in MVAL.
274 *
275  DO 60 im = 1, nm
276  m = mval( im )
277 *
278 * Do for each value of P in PVAL.
279 *
280  DO 50 ip = 1, np
281  p = pval( ip )
282 *
283 * Do for each value of N in NVAL.
284 *
285  DO 40 in = 1, nn
286  n = nval( in )
287 *
288  DO 30 imat = 1, ntypes
289 *
290 * Do the tests only if DOTYPE( IMAT ) is true.
291 *
292  IF( .NOT.dotype( imat ) )
293  $ GO TO 30
294 *
295 * Test CGGRQF
296 *
297 * Set up parameters with SLATB9 and generate test
298 * matrices A and B with CLATMS.
299 *
300  CALL slatb9( 'GRQ', imat, m, p, n, TYPE, kla, kua,
301  $ klb, kub, anorm, bnorm, modea, modeb,
302  $ cndnma, cndnmb, dista, distb )
303 *
304  CALL clatms( m, n, dista, iseed, TYPE, rwork, modea,
305  $ cndnma, anorm, kla, kua, 'No packing', a,
306  $ lda, work, iinfo )
307  IF( iinfo.NE.0 ) THEN
308  WRITE( nout, fmt = 9999 )iinfo
309  info = abs( iinfo )
310  GO TO 30
311  END IF
312 *
313  CALL clatms( p, n, distb, iseed, TYPE, rwork, modeb,
314  $ cndnmb, bnorm, klb, kub, 'No packing', b,
315  $ ldb, work, iinfo )
316  IF( iinfo.NE.0 ) THEN
317  WRITE( nout, fmt = 9999 )iinfo
318  info = abs( iinfo )
319  GO TO 30
320  END IF
321 *
322  nt = 4
323 *
324  CALL cgrqts( m, p, n, a, af, aq, ar, lda, taua, b, bf,
325  $ bz, bt, bwk, ldb, taub, work, lwork,
326  $ rwork, result )
327 *
328 * Print information about the tests that did not
329 * pass the threshold.
330 *
331  DO 10 i = 1, nt
332  IF( result( i ).GE.thresh ) THEN
333  IF( nfail.EQ.0 .AND. firstt ) THEN
334  firstt = .false.
335  CALL alahdg( nout, 'GRQ' )
336  END IF
337  WRITE( nout, fmt = 9998 )m, p, n, imat, i,
338  $ result( i )
339  nfail = nfail + 1
340  END IF
341  10 CONTINUE
342  nrun = nrun + nt
343 *
344 * Test CGGQRF
345 *
346 * Set up parameters with SLATB9 and generate test
347 * matrices A and B with CLATMS.
348 *
349  CALL slatb9( 'GQR', imat, m, p, n, TYPE, kla, kua,
350  $ klb, kub, anorm, bnorm, modea, modeb,
351  $ cndnma, cndnmb, dista, distb )
352 *
353  CALL clatms( n, m, dista, iseed, TYPE, rwork, modea,
354  $ cndnma, anorm, kla, kua, 'No packing', a,
355  $ lda, work, iinfo )
356  IF( iinfo.NE.0 ) THEN
357  WRITE( nout, fmt = 9999 )iinfo
358  info = abs( iinfo )
359  GO TO 30
360  END IF
361 *
362  CALL clatms( n, p, distb, iseed, TYPE, rwork, modea,
363  $ cndnma, bnorm, klb, kub, 'No packing', b,
364  $ ldb, work, iinfo )
365  IF( iinfo.NE.0 ) THEN
366  WRITE( nout, fmt = 9999 )iinfo
367  info = abs( iinfo )
368  GO TO 30
369  END IF
370 *
371  nt = 4
372 *
373  CALL cgqrts( n, m, p, a, af, aq, ar, lda, taua, b, bf,
374  $ bz, bt, bwk, ldb, taub, work, lwork,
375  $ rwork, result )
376 *
377 * Print information about the tests that did not
378 * pass the threshold.
379 *
380  DO 20 i = 1, nt
381  IF( result( i ).GE.thresh ) THEN
382  IF( nfail.EQ.0 .AND. firstt ) THEN
383  firstt = .false.
384  CALL alahdg( nout, path )
385  END IF
386  WRITE( nout, fmt = 9997 )n, m, p, imat, i,
387  $ result( i )
388  nfail = nfail + 1
389  END IF
390  20 CONTINUE
391  nrun = nrun + nt
392 *
393  30 CONTINUE
394  40 CONTINUE
395  50 CONTINUE
396  60 CONTINUE
397 *
398 * Print a summary of the results.
399 *
400  CALL alasum( path, nout, nfail, nrun, 0 )
401 *
402  9999 FORMAT( ' CLATMS in CCKGQR: INFO = ', i5 )
403  9998 FORMAT( ' M=', i4, ' P=', i4, ', N=', i4, ', type ', i2,
404  $ ', test ', i2, ', ratio=', g13.6 )
405  9997 FORMAT( ' N=', i4, ' M=', i4, ', P=', i4, ', type ', i2,
406  $ ', test ', i2, ', ratio=', g13.6 )
407  RETURN
408 *
409 * End of CCKGQR
410 *
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
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 clatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
CLATMS
Definition: clatms.f:334
subroutine cgrqts(M, P, N, A, AF, Q, R, LDA, TAUA, B, BF, Z, T, BWK, LDB, TAUB, WORK, LWORK, RWORK, RESULT)
CGRQTS
Definition: cgrqts.f:178
subroutine cgqrts(N, M, P, A, AF, Q, R, LDA, TAUA, B, BF, Z, T, BWK, LDB, TAUB, WORK, LWORK, RWORK, RESULT)
CGQRTS
Definition: cgqrts.f:178
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: