1*> \brief \b CCKGLM
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 CCKGLM( NN, NVAL, MVAL, PVAL, NMATS, ISEED, THRESH,
12*                          NMAX, A, AF, B, BF, X, WORK, RWORK, NIN, NOUT,
13*                          INFO )
14*
15*       .. Scalar Arguments ..
16*       INTEGER            INFO, NIN, NMATS, NMAX, NN, NOUT
17*       REAL               THRESH
18*       ..
19*       .. Array Arguments ..
20*       INTEGER            ISEED( 4 ), MVAL( * ), NVAL( * ), PVAL( * )
21*       REAL               RWORK( * )
22*       COMPLEX            A( * ), AF( * ), B( * ), BF( * ), WORK( * ),
23*      $                   X( * )
24*       ..
25*
26*
27*> \par Purpose:
28*  =============
29*>
30*> \verbatim
31*>
32*> CCKGLM tests CGGGLM - subroutine for solving generalized linear
33*>                       model problem.
34*> \endverbatim
35*
36*  Arguments:
37*  ==========
38*
39*> \param[in] NN
40*> \verbatim
41*>          NN is INTEGER
42*>          The number of values of N, M and P contained in the vectors
43*>          NVAL, MVAL and PVAL.
44*> \endverbatim
45*>
46*> \param[in] NVAL
47*> \verbatim
48*>          NVAL is INTEGER array, dimension (NN)
49*>          The values of the matrix row dimension N.
50*> \endverbatim
51*>
52*> \param[in] MVAL
53*> \verbatim
54*>          MVAL is INTEGER array, dimension (NN)
55*>          The values of the matrix column dimension M.
56*> \endverbatim
57*>
58*> \param[in] PVAL
59*> \verbatim
60*>          PVAL is INTEGER array, dimension (NN)
61*>          The values of the matrix column dimension P.
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 REAL
87*>          The threshold value for the test ratios.  A result is
88*>          included in the output file if RESID >= 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 array, dimension (NMAX*NMAX)
102*> \endverbatim
103*>
104*> \param[out] AF
105*> \verbatim
106*>          AF is COMPLEX array, dimension (NMAX*NMAX)
107*> \endverbatim
108*>
109*> \param[out] B
110*> \verbatim
111*>          B is COMPLEX array, dimension (NMAX*NMAX)
112*> \endverbatim
113*>
114*> \param[out] BF
115*> \verbatim
116*>          BF is COMPLEX array, dimension (NMAX*NMAX)
117*> \endverbatim
118*>
119*> \param[out] X
120*> \verbatim
121*>          X is COMPLEX array, dimension (4*NMAX)
122*> \endverbatim
123*>
124*> \param[out] RWORK
125*> \verbatim
126*>          RWORK is REAL array, dimension (NMAX)
127*> \endverbatim
128*>
129*> \param[out] WORK
130*> \verbatim
131*>          WORK is COMPLEX array, dimension (NMAX*NMAX)
132*> \endverbatim
133*>
134*> \param[in] NIN
135*> \verbatim
136*>          NIN is INTEGER
137*>          The unit number for input.
138*> \endverbatim
139*>
140*> \param[in] NOUT
141*> \verbatim
142*>          NOUT is INTEGER
143*>          The unit number for output.
144*> \endverbatim
145*>
146*> \param[out] INFO
147*> \verbatim
148*>          INFO is INTEGER
149*>          = 0 :  successful exit
150*>          > 0 :  If CLATMS returns an error code, the absolute value
151*>                 of it is returned.
152*> \endverbatim
153*
154*  Authors:
155*  ========
156*
157*> \author Univ. of Tennessee
158*> \author Univ. of California Berkeley
159*> \author Univ. of Colorado Denver
160*> \author NAG Ltd.
161*
162*> \ingroup complex_eig
163*
164*  =====================================================================
165      SUBROUTINE CCKGLM( NN, NVAL, MVAL, PVAL, NMATS, ISEED, THRESH,
166     $                   NMAX, A, AF, B, BF, X, WORK, RWORK, NIN, NOUT,
167     $                   INFO )
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      REAL               THRESH
176*     ..
177*     .. Array Arguments ..
178      INTEGER            ISEED( 4 ), MVAL( * ), NVAL( * ), PVAL( * )
179      REAL               RWORK( * )
180      COMPLEX            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      REAL               ANORM, BNORM, CNDNMA, CNDNMB, RESID
197*     ..
198*     .. Local Arrays ..
199      LOGICAL            DOTYPE( NTYPES )
200*     ..
201*     .. External Functions ..
202      COMPLEX            CLARND
203      EXTERNAL           CLARND
204*     ..
205*     .. External Subroutines ..
206      EXTERNAL           ALAHDG, ALAREQ, ALASUM, CGLMTS, CLATMS, SLATB9
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 SLATB9 and generate test
258*           matrices A and B with CLATMS.
259*
260            CALL SLATB9( PATH, IMAT, M, P, N, TYPE, KLA, KUA, KLB, KUB,
261     $                   ANORM, BNORM, MODEA, MODEB, CNDNMA, CNDNMB,
262     $                   DISTA, DISTB )
263*
264            CALL CLATMS( 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 CLATMS( 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 ) = CLARND( 2, ISEED )
286   20       CONTINUE
287*
288            CALL CGLMTS( 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( ' CLATMS in CCKGLM 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 CCKGLM
321*
322      END
323