LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cckglm ( integer  NN,
integer, dimension( * )  NVAL,
integer, dimension( * )  MVAL,
integer, dimension( * )  PVAL,
integer  NMATS,
integer, dimension( 4 )  ISEED,
real  THRESH,
integer  NMAX,
complex, dimension( * )  A,
complex, dimension( * )  AF,
complex, dimension( * )  B,
complex, dimension( * )  BF,
complex, dimension( * )  X,
complex, dimension( * )  WORK,
real, dimension( * )  RWORK,
integer  NIN,
integer  NOUT,
integer  INFO 
)

CCKGLM

Purpose:
 CCKGLM tests CGGGLM - 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 REAL
          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 array, dimension (NMAX*NMAX)
[out]AF
          AF is COMPLEX array, dimension (NMAX*NMAX)
[out]B
          B is COMPLEX array, dimension (NMAX*NMAX)
[out]BF
          BF is COMPLEX array, dimension (NMAX*NMAX)
[out]X
          X is COMPLEX array, dimension (4*NMAX)
[out]RWORK
          RWORK is REAL array, dimension (NMAX)
[out]WORK
          WORK is COMPLEX 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 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.
Date
November 2011

Definition at line 170 of file cckglm.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: