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

◆ cckgqr()

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.

Definition at line 208 of file cckgqr.f.

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