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

◆ zckglm()

subroutine zckglm ( integer  nn,
integer, dimension( * )  nval,
integer, dimension( * )  mval,
integer, dimension( * )  pval,
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( * )  x,
complex*16, dimension( * )  work,
double precision, dimension( * )  rwork,
integer  nin,
integer  nout,
integer  info 
)

ZCKGLM

Purpose:
 ZCKGLM tests ZGGGLM - subroutine for solving generalized linear
                       model problem.
Parameters
[in]NN
          NN is INTEGER
          The number of values of N, M and P contained in the vectors
          NVAL, MVAL and PVAL.
[in]NVAL
          NVAL is INTEGER array, dimension (NN)
          The values of the matrix row dimension N.
[in]MVAL
          MVAL is INTEGER array, dimension (NN)
          The values of the matrix column dimension M.
[in]PVAL
          PVAL is INTEGER array, dimension (NN)
          The values of the matrix column dimension P.
[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 RESID >= 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]X
          X is COMPLEX*16 array, dimension (4*NMAX)
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (NMAX)
[out]WORK
          WORK is COMPLEX*16 array, dimension (NMAX*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 165 of file zckglm.f.

168*
169* -- LAPACK test routine --
170* -- LAPACK is a software package provided by Univ. of Tennessee, --
171* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
172*
173* .. Scalar Arguments ..
174 INTEGER INFO, NIN, NMATS, NMAX, NN, NOUT
175 DOUBLE PRECISION THRESH
176* ..
177* .. Array Arguments ..
178 INTEGER ISEED( 4 ), MVAL( * ), NVAL( * ), PVAL( * )
179 DOUBLE PRECISION RWORK( * )
180 COMPLEX*16 A( * ), AF( * ), B( * ), BF( * ), WORK( * ),
181 $ X( * )
182* ..
183*
184* =====================================================================
185*
186* .. Parameters ..
187 INTEGER NTYPES
188 parameter( ntypes = 8 )
189* ..
190* .. Local Scalars ..
191 LOGICAL FIRSTT
192 CHARACTER DISTA, DISTB, TYPE
193 CHARACTER*3 PATH
194 INTEGER I, IINFO, IK, IMAT, KLA, KLB, KUA, KUB, LDA,
195 $ LDB, LWORK, M, MODEA, MODEB, N, NFAIL, NRUN, P
196 DOUBLE PRECISION ANORM, BNORM, CNDNMA, CNDNMB, RESID
197* ..
198* .. Local Arrays ..
199 LOGICAL DOTYPE( NTYPES )
200* ..
201* .. External Functions ..
202 COMPLEX*16 ZLARND
203 EXTERNAL zlarnd
204* ..
205* .. External Subroutines ..
206 EXTERNAL alahdg, alareq, alasum, dlatb9, zglmts, zlatms
207* ..
208* .. Intrinsic Functions ..
209 INTRINSIC abs
210* ..
211* .. Executable Statements ..
212*
213* Initialize constants.
214*
215 path( 1: 3 ) = 'GLM'
216 info = 0
217 nrun = 0
218 nfail = 0
219 firstt = .true.
220 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
221 lda = nmax
222 ldb = nmax
223 lwork = nmax*nmax
224*
225* Check for valid input values.
226*
227 DO 10 ik = 1, nn
228 m = mval( ik )
229 p = pval( ik )
230 n = nval( ik )
231 IF( m.GT.n .OR. n.GT.m+p ) THEN
232 IF( firstt ) THEN
233 WRITE( nout, fmt = * )
234 firstt = .false.
235 END IF
236 WRITE( nout, fmt = 9997 )m, p, n
237 END IF
238 10 CONTINUE
239 firstt = .true.
240*
241* Do for each value of M in MVAL.
242*
243 DO 40 ik = 1, nn
244 m = mval( ik )
245 p = pval( ik )
246 n = nval( ik )
247 IF( m.GT.n .OR. n.GT.m+p )
248 $ GO TO 40
249*
250 DO 30 imat = 1, ntypes
251*
252* Do the tests only if DOTYPE( IMAT ) is true.
253*
254 IF( .NOT.dotype( imat ) )
255 $ GO TO 30
256*
257* Set up parameters with DLATB9 and generate test
258* matrices A and B with ZLATMS.
259*
260 CALL dlatb9( path, imat, m, p, n, TYPE, KLA, KUA, KLB, KUB,
261 $ ANORM, BNORM, MODEA, MODEB, CNDNMA, CNDNMB,
262 $ DISTA, DISTB )
263*
264 CALL zlatms( n, m, dista, iseed, TYPE, RWORK, MODEA, CNDNMA,
265 $ ANORM, KLA, KUA, 'No packing', A, LDA, WORK,
266 $ IINFO )
267 IF( iinfo.NE.0 ) THEN
268 WRITE( nout, fmt = 9999 )iinfo
269 info = abs( iinfo )
270 GO TO 30
271 END IF
272*
273 CALL zlatms( n, p, distb, iseed, TYPE, RWORK, MODEB, CNDNMB,
274 $ BNORM, KLB, KUB, 'No packing', B, LDB, WORK,
275 $ IINFO )
276 IF( iinfo.NE.0 ) THEN
277 WRITE( nout, fmt = 9999 )iinfo
278 info = abs( iinfo )
279 GO TO 30
280 END IF
281*
282* Generate random left hand side vector of GLM
283*
284 DO 20 i = 1, n
285 x( i ) = zlarnd( 2, iseed )
286 20 CONTINUE
287*
288 CALL zglmts( n, m, p, a, af, lda, b, bf, ldb, x,
289 $ x( nmax+1 ), x( 2*nmax+1 ), x( 3*nmax+1 ),
290 $ work, lwork, rwork, resid )
291*
292* Print information about the tests that did not
293* pass the threshold.
294*
295 IF( resid.GE.thresh ) THEN
296 IF( nfail.EQ.0 .AND. firstt ) THEN
297 firstt = .false.
298 CALL alahdg( nout, path )
299 END IF
300 WRITE( nout, fmt = 9998 )n, m, p, imat, 1, resid
301 nfail = nfail + 1
302 END IF
303 nrun = nrun + 1
304*
305 30 CONTINUE
306 40 CONTINUE
307*
308* Print a summary of the results.
309*
310 CALL alasum( path, nout, nfail, nrun, 0 )
311*
312 9999 FORMAT( ' ZLATMS in ZCKGLM INFO = ', i5 )
313 9998 FORMAT( ' N=', i4, ' M=', i4, ', P=', i4, ', type ', i2,
314 $ ', test ', i2, ', ratio=', g13.6 )
315 9997 FORMAT( ' *** Invalid input for GLM: M = ', i6, ', P = ', i6,
316 $ ', N = ', i6, ';', / ' must satisfy M <= N <= M+P ',
317 $ '(this set of values will be skipped)' )
318 RETURN
319*
320* End of ZCKGLM
321*
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 zglmts(n, m, p, a, af, lda, b, bf, ldb, d, df, x, u, work, lwork, rwork, result)
ZGLMTS
Definition zglmts.f:146
complex *16 function zlarnd(idist, iseed)
ZLARND
Definition zlarnd.f:75
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: