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

◆ zckgsv()

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

ZCKGSV

Purpose:
 ZCKGSV tests ZGGSVD:
        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 DOUBLE PRECISION
          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*16 array, dimension (NMAX*NMAX)
[out]AF
          AF is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]B
          B is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]BF
          BF is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]U
          U is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]V
          V is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]Q
          Q is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]ALPHA
          ALPHA is DOUBLE PRECISION array, dimension (NMAX)
[out]BETA
          BETA is DOUBLE PRECISION array, dimension (NMAX)
[out]R
          R is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]IWORK
          IWORK is INTEGER array, dimension (NMAX)
[out]WORK
          WORK is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]RWORK
          RWORK is DOUBLE PRECISION 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 ZLATMS 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 zckgsv.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 DOUBLE PRECISION THRESH
206* ..
207* .. Array Arguments ..
208 INTEGER ISEED( 4 ), IWORK( * ), MVAL( * ), NVAL( * ),
209 $ PVAL( * )
210 DOUBLE PRECISION ALPHA( * ), BETA( * ), RWORK( * )
211 COMPLEX*16 A( * ), AF( * ), B( * ), BF( * ), Q( * ),
212 $ R( * ), U( * ), 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 DOUBLE PRECISION ANORM, BNORM, CNDNMA, CNDNMB
231* ..
232* .. Local Arrays ..
233 LOGICAL DOTYPE( NTYPES )
234 DOUBLE PRECISION 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 DLATB9 and generate test
275* matrices A and B with ZLATMS.
276*
277 CALL dlatb9( 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 zlatms( 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* Generate P by N matrix B
293*
294 CALL zlatms( p, n, distb, iseed, TYPE, RWORK, MODEB, CNDNMB,
295 $ BNORM, KLB, KUB, 'No packing', B, LDB, WORK,
296 $ IINFO )
297 IF( iinfo.NE.0 ) THEN
298 WRITE( nout, fmt = 9999 )iinfo
299 info = abs( iinfo )
300 GO TO 20
301 END IF
302*
303 nt = 6
304*
305 CALL zgsvts3( m, p, n, a, af, lda, b, bf, ldb, u, ldu, v,
306 $ ldv, q, ldq, alpha, beta, r, ldr, iwork, work,
307 $ lwork, rwork, result )
308*
309* Print information about the tests that did not
310* pass the threshold.
311*
312 DO 10 i = 1, nt
313 IF( result( i ).GE.thresh ) THEN
314 IF( nfail.EQ.0 .AND. firstt ) THEN
315 firstt = .false.
316 CALL alahdg( nout, path )
317 END IF
318 WRITE( nout, fmt = 9998 )m, p, n, imat, i,
319 $ result( i )
320 nfail = nfail + 1
321 END IF
322 10 CONTINUE
323 nrun = nrun + nt
324*
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( ' ZLATMS in ZCKGSV 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 ZCKGSV
338*
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 dlatb9(path, imat, m, p, n, type, kla, kua, klb, kub, anorm, bnorm, modea, modeb, cndnma, cndnmb, dista, distb)
DLATB9
Definition dlatb9.f:170
subroutine zgsvts3(m, p, n, a, af, lda, b, bf, ldb, u, ldu, v, ldv, q, ldq, alpha, beta, r, ldr, iwork, work, lwork, rwork, result)
ZGSVTS3
Definition zgsvts3.f:209
subroutine zlatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
ZLATMS
Definition zlatms.f:332
Here is the call graph for this function:
Here is the caller graph for this function: