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

◆ dckglm()

subroutine dckglm ( integer  nn,
integer, dimension( * )  mval,
integer, dimension( * )  pval,
integer, dimension( * )  nval,
integer  nmats,
integer, dimension( 4 )  iseed,
double precision  thresh,
integer  nmax,
double precision, dimension( * )  a,
double precision, dimension( * )  af,
double precision, dimension( * )  b,
double precision, dimension( * )  bf,
double precision, dimension( * )  x,
double precision, dimension( * )  work,
double precision, dimension( * )  rwork,
integer  nin,
integer  nout,
integer  info 
)

DCKGLM

Purpose:
 DCKGLM tests DGGGLM - 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]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]NVAL
          NVAL is INTEGER array, dimension (NN)
          The values of the matrix 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 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 DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]AF
          AF is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]B
          B is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]BF
          BF is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]X
          X is DOUBLE PRECISION array, dimension (4*NMAX)
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (NMAX)
[out]WORK
          WORK is DOUBLE PRECISION 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 DLATMS 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 164 of file dckglm.f.

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