LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zckgsv.f
Go to the documentation of this file.
1 *> \brief \b ZCKGSV
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE ZCKGSV( NM, MVAL, PVAL, NVAL, NMATS, ISEED, THRESH,
12 * NMAX, A, AF, B, BF, U, V, Q, ALPHA, BETA, R,
13 * IWORK, WORK, RWORK, NIN, NOUT, INFO )
14 *
15 * .. Scalar Arguments ..
16 * INTEGER INFO, NIN, NM, NMATS, NMAX, NOUT
17 * DOUBLE PRECISION THRESH
18 * ..
19 * .. Array Arguments ..
20 * INTEGER ISEED( 4 ), IWORK( * ), MVAL( * ), NVAL( * ),
21 * $ PVAL( * )
22 * DOUBLE PRECISION ALPHA( * ), BETA( * ), RWORK( * )
23 * COMPLEX*16 A( * ), AF( * ), B( * ), BF( * ), Q( * ),
24 * $ R( * ), U( * ), V( * ), WORK( * )
25 * ..
26 *
27 *
28 *> \par Purpose:
29 * =============
30 *>
31 *> \verbatim
32 *>
33 *> ZCKGSV tests ZGGSVD:
34 *> the GSVD for M-by-N matrix A and P-by-N matrix B.
35 *> \endverbatim
36 *
37 * Arguments:
38 * ==========
39 *
40 *> \param[in] NM
41 *> \verbatim
42 *> NM is INTEGER
43 *> The number of values of M contained in the vector MVAL.
44 *> \endverbatim
45 *>
46 *> \param[in] MVAL
47 *> \verbatim
48 *> MVAL is INTEGER array, dimension (NM)
49 *> The values of the matrix row dimension M.
50 *> \endverbatim
51 *>
52 *> \param[in] PVAL
53 *> \verbatim
54 *> PVAL is INTEGER array, dimension (NP)
55 *> The values of the matrix row dimension P.
56 *> \endverbatim
57 *>
58 *> \param[in] NVAL
59 *> \verbatim
60 *> NVAL is INTEGER array, dimension (NN)
61 *> The values of the matrix column dimension N.
62 *> \endverbatim
63 *>
64 *> \param[in] NMATS
65 *> \verbatim
66 *> NMATS is INTEGER
67 *> The number of matrix types to be tested for each combination
68 *> of matrix dimensions. If NMATS >= NTYPES (the maximum
69 *> number of matrix types), then all the different types are
70 *> generated for testing. If NMATS < NTYPES, another input line
71 *> is read to get the numbers of the matrix types to be used.
72 *> \endverbatim
73 *>
74 *> \param[in,out] ISEED
75 *> \verbatim
76 *> ISEED is INTEGER array, dimension (4)
77 *> On entry, the seed of the random number generator. The array
78 *> elements should be between 0 and 4095, otherwise they will be
79 *> reduced mod 4096, and ISEED(4) must be odd.
80 *> On exit, the next seed in the random number sequence after
81 *> all the test matrices have been generated.
82 *> \endverbatim
83 *>
84 *> \param[in] THRESH
85 *> \verbatim
86 *> THRESH is DOUBLE PRECISION
87 *> The threshold value for the test ratios. A result is
88 *> included in the output file if RESULT >= THRESH. To have
89 *> every test ratio printed, use THRESH = 0.
90 *> \endverbatim
91 *>
92 *> \param[in] NMAX
93 *> \verbatim
94 *> NMAX is INTEGER
95 *> The maximum value permitted for M or N, used in dimensioning
96 *> the work arrays.
97 *> \endverbatim
98 *>
99 *> \param[out] A
100 *> \verbatim
101 *> A is COMPLEX*16 array, dimension (NMAX*NMAX)
102 *> \endverbatim
103 *>
104 *> \param[out] AF
105 *> \verbatim
106 *> AF is COMPLEX*16 array, dimension (NMAX*NMAX)
107 *> \endverbatim
108 *>
109 *> \param[out] B
110 *> \verbatim
111 *> B is COMPLEX*16 array, dimension (NMAX*NMAX)
112 *> \endverbatim
113 *>
114 *> \param[out] BF
115 *> \verbatim
116 *> BF is COMPLEX*16 array, dimension (NMAX*NMAX)
117 *> \endverbatim
118 *>
119 *> \param[out] U
120 *> \verbatim
121 *> U is COMPLEX*16 array, dimension (NMAX*NMAX)
122 *> \endverbatim
123 *>
124 *> \param[out] V
125 *> \verbatim
126 *> V is COMPLEX*16 array, dimension (NMAX*NMAX)
127 *> \endverbatim
128 *>
129 *> \param[out] Q
130 *> \verbatim
131 *> Q is COMPLEX*16 array, dimension (NMAX*NMAX)
132 *> \endverbatim
133 *>
134 *> \param[out] ALPHA
135 *> \verbatim
136 *> ALPHA is DOUBLE PRECISION array, dimension (NMAX)
137 *> \endverbatim
138 *>
139 *> \param[out] BETA
140 *> \verbatim
141 *> BETA is DOUBLE PRECISION array, dimension (NMAX)
142 *> \endverbatim
143 *>
144 *> \param[out] R
145 *> \verbatim
146 *> R is COMPLEX*16 array, dimension (NMAX*NMAX)
147 *> \endverbatim
148 *>
149 *> \param[out] IWORK
150 *> \verbatim
151 *> IWORK is INTEGER array, dimension (NMAX)
152 *> \endverbatim
153 *>
154 *> \param[out] WORK
155 *> \verbatim
156 *> WORK is COMPLEX*16 array, dimension (NMAX*NMAX)
157 *> \endverbatim
158 *>
159 *> \param[out] RWORK
160 *> \verbatim
161 *> RWORK is DOUBLE PRECISION array, dimension (NMAX)
162 *> \endverbatim
163 *>
164 *> \param[in] NIN
165 *> \verbatim
166 *> NIN is INTEGER
167 *> The unit number for input.
168 *> \endverbatim
169 *>
170 *> \param[in] NOUT
171 *> \verbatim
172 *> NOUT is INTEGER
173 *> The unit number for output.
174 *> \endverbatim
175 *>
176 *> \param[out] INFO
177 *> \verbatim
178 *> INFO is INTEGER
179 *> = 0 : successful exit
180 *> > 0 : If ZLATMS returns an error code, the absolute value
181 *> of it is returned.
182 *> \endverbatim
183 *
184 * Authors:
185 * ========
186 *
187 *> \author Univ. of Tennessee
188 *> \author Univ. of California Berkeley
189 *> \author Univ. of Colorado Denver
190 *> \author NAG Ltd.
191 *
192 *> \date November 2015
193 *
194 *> \ingroup complex16_eig
195 *
196 * =====================================================================
197  SUBROUTINE zckgsv( NM, MVAL, PVAL, NVAL, NMATS, ISEED, THRESH,
198  $ nmax, a, af, b, bf, u, v, q, alpha, beta, r,
199  $ iwork, work, rwork, nin, nout, info )
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  DOUBLE PRECISION THRESH
209 * ..
210 * .. Array Arguments ..
211  INTEGER ISEED( 4 ), IWORK( * ), MVAL( * ), NVAL( * ),
212  $ pval( * )
213  DOUBLE PRECISION ALPHA( * ), BETA( * ), RWORK( * )
214  COMPLEX*16 A( * ), AF( * ), B( * ), BF( * ), Q( * ),
215  $ r( * ), u( * ), 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  DOUBLE PRECISION ANORM, BNORM, CNDNMA, CNDNMB
234 * ..
235 * .. Local Arrays ..
236  LOGICAL DOTYPE( ntypes )
237  DOUBLE PRECISION RESULT( ntests )
238 * ..
239 * .. External Subroutines ..
240  EXTERNAL alahdg, alareq, alasum, dlatb9, zgsvts3, zlatms
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 DLATB9 and generate test
278 * matrices A and B with ZLATMS.
279 *
280  CALL dlatb9( 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 zlatms( 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 * Generate P by N matrix B
296 *
297  CALL zlatms( p, n, distb, iseed, TYPE, RWORK, MODEB, CNDNMB,
298  $ bnorm, klb, kub, 'No packing', b, ldb, work,
299  $ iinfo )
300  IF( iinfo.NE.0 ) THEN
301  WRITE( nout, fmt = 9999 )iinfo
302  info = abs( iinfo )
303  GO TO 20
304  END IF
305 *
306  nt = 6
307 *
308  CALL zgsvts3( m, p, n, a, af, lda, b, bf, ldb, u, ldu, v,
309  $ ldv, q, ldq, alpha, beta, r, ldr, iwork, work,
310  $ lwork, rwork, result )
311 *
312 * Print information about the tests that did not
313 * pass the threshold.
314 *
315  DO 10 i = 1, nt
316  IF( result( i ).GE.thresh ) THEN
317  IF( nfail.EQ.0 .AND. firstt ) THEN
318  firstt = .false.
319  CALL alahdg( nout, path )
320  END IF
321  WRITE( nout, fmt = 9998 )m, p, n, imat, i,
322  $ result( i )
323  nfail = nfail + 1
324  END IF
325  10 CONTINUE
326  nrun = nrun + nt
327 *
328  20 CONTINUE
329  30 CONTINUE
330 *
331 * Print a summary of the results.
332 *
333  CALL alasum( path, nout, nfail, nrun, 0 )
334 *
335  9999 FORMAT( ' ZLATMS in ZCKGSV INFO = ', i5 )
336  9998 FORMAT( ' M=', i4, ' P=', i4, ', N=', i4, ', type ', i2,
337  $ ', test ', i2, ', ratio=', g13.6 )
338  RETURN
339 *
340 * End of ZCKGSV
341 *
342  END
subroutine zckgsv(NM, MVAL, PVAL, NVAL, NMATS, ISEED, THRESH, NMAX, A, AF, B, BF, U, V, Q, ALPHA, BETA, R, IWORK, WORK, RWORK, NIN, NOUT, INFO)
ZCKGSV
Definition: zckgsv.f:200
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
subroutine dlatb9(PATH, IMAT, M, P, N, TYPE, KLA, KUA, KLB, KUB, ANORM, BNORM, MODEA, MODEB, CNDNMA, CNDNMB, DISTA, DISTB)
DLATB9
Definition: dlatb9.f:172
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:211
subroutine zlatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
ZLATMS
Definition: zlatms.f:334
subroutine alahdg(IOUNIT, PATH)
ALAHDG
Definition: alahdg.f:64
subroutine alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75