LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
scklse.f
Go to the documentation of this file.
1 *> \brief \b SCKLSE
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 SCKLSE( NN, MVAL, PVAL, NVAL, 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 A( * ), AF( * ), B( * ), BF( * ), RWORK( * ),
22 * $ WORK( * ), X( * )
23 * ..
24 *
25 *
26 *> \par Purpose:
27 * =============
28 *>
29 *> \verbatim
30 *>
31 *> SCKLSE tests SGGLSE - a subroutine for solving linear equality
32 *> constrained least square problem (LSE).
33 *> \endverbatim
34 *
35 * Arguments:
36 * ==========
37 *
38 *> \param[in] NN
39 *> \verbatim
40 *> NN is INTEGER
41 *> The number of values of (M,P,N) contained in the vectors
42 *> (MVAL, PVAL, NVAL).
43 *> \endverbatim
44 *>
45 *> \param[in] MVAL
46 *> \verbatim
47 *> MVAL is INTEGER array, dimension (NN)
48 *> The values of the matrix row(column) dimension M.
49 *> \endverbatim
50 *>
51 *> \param[in] PVAL
52 *> \verbatim
53 *> PVAL is INTEGER array, dimension (NN)
54 *> The values of the matrix row(column) dimension P.
55 *> \endverbatim
56 *>
57 *> \param[in] NVAL
58 *> \verbatim
59 *> NVAL is INTEGER array, dimension (NN)
60 *> The values of the matrix column(row) dimension N.
61 *> \endverbatim
62 *>
63 *> \param[in] NMATS
64 *> \verbatim
65 *> NMATS is INTEGER
66 *> The number of matrix types to be tested for each combination
67 *> of matrix dimensions. If NMATS >= NTYPES (the maximum
68 *> number of matrix types), then all the different types are
69 *> generated for testing. If NMATS < NTYPES, another input line
70 *> is read to get the numbers of the matrix types to be used.
71 *> \endverbatim
72 *>
73 *> \param[in,out] ISEED
74 *> \verbatim
75 *> ISEED is INTEGER array, dimension (4)
76 *> On entry, the seed of the random number generator. The array
77 *> elements should be between 0 and 4095, otherwise they will be
78 *> reduced mod 4096, and ISEED(4) must be odd.
79 *> On exit, the next seed in the random number sequence after
80 *> all the test matrices have been generated.
81 *> \endverbatim
82 *>
83 *> \param[in] THRESH
84 *> \verbatim
85 *> THRESH is REAL
86 *> The threshold value for the test ratios. A result is
87 *> included in the output file if RESULT >= THRESH. To have
88 *> every test ratio printed, use THRESH = 0.
89 *> \endverbatim
90 *>
91 *> \param[in] NMAX
92 *> \verbatim
93 *> NMAX is INTEGER
94 *> The maximum value permitted for M or N, used in dimensioning
95 *> the work arrays.
96 *> \endverbatim
97 *>
98 *> \param[out] A
99 *> \verbatim
100 *> A is REAL array, dimension (NMAX*NMAX)
101 *> \endverbatim
102 *>
103 *> \param[out] AF
104 *> \verbatim
105 *> AF is REAL array, dimension (NMAX*NMAX)
106 *> \endverbatim
107 *>
108 *> \param[out] B
109 *> \verbatim
110 *> B is REAL array, dimension (NMAX*NMAX)
111 *> \endverbatim
112 *>
113 *> \param[out] BF
114 *> \verbatim
115 *> BF is REAL array, dimension (NMAX*NMAX)
116 *> \endverbatim
117 *>
118 *> \param[out] X
119 *> \verbatim
120 *> X is REAL array, dimension (5*NMAX)
121 *> \endverbatim
122 *>
123 *> \param[out] WORK
124 *> \verbatim
125 *> WORK is REAL array, dimension (NMAX*NMAX)
126 *> \endverbatim
127 *>
128 *> \param[out] RWORK
129 *> \verbatim
130 *> RWORK is REAL array, dimension (NMAX)
131 *> \endverbatim
132 *>
133 *> \param[in] NIN
134 *> \verbatim
135 *> NIN is INTEGER
136 *> The unit number for input.
137 *> \endverbatim
138 *>
139 *> \param[in] NOUT
140 *> \verbatim
141 *> NOUT is INTEGER
142 *> The unit number for output.
143 *> \endverbatim
144 *>
145 *> \param[out] INFO
146 *> \verbatim
147 *> INFO is INTEGER
148 *> = 0 : successful exit
149 *> > 0 : If SLATMS returns an error code, the absolute value
150 *> of it is returned.
151 *> \endverbatim
152 *
153 * Authors:
154 * ========
155 *
156 *> \author Univ. of Tennessee
157 *> \author Univ. of California Berkeley
158 *> \author Univ. of Colorado Denver
159 *> \author NAG Ltd.
160 *
161 *> \date November 2011
162 *
163 *> \ingroup single_eig
164 *
165 * =====================================================================
166  SUBROUTINE scklse( NN, MVAL, PVAL, NVAL, NMATS, ISEED, THRESH,
167  $ nmax, a, af, b, bf, x, work, rwork, nin, nout,
168  $ info )
169 *
170 * -- LAPACK test routine (version 3.4.0) --
171 * -- LAPACK is a software package provided by Univ. of Tennessee, --
172 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
173 * November 2011
174 *
175 * .. Scalar Arguments ..
176  INTEGER INFO, NIN, NMATS, NMAX, NN, NOUT
177  REAL THRESH
178 * ..
179 * .. Array Arguments ..
180  INTEGER ISEED( 4 ), MVAL( * ), NVAL( * ), PVAL( * )
181  REAL A( * ), AF( * ), B( * ), BF( * ), RWORK( * ),
182  $ work( * ), x( * )
183 * ..
184 *
185 * =====================================================================
186 *
187 * .. Parameters ..
188  INTEGER NTESTS
189  parameter ( ntests = 7 )
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,
199  $ nt, p
200  REAL ANORM, BNORM, CNDNMA, CNDNMB
201 * ..
202 * .. Local Arrays ..
203  LOGICAL DOTYPE( ntypes )
204  REAL RESULT( ntests )
205 * ..
206 * .. External Subroutines ..
207  EXTERNAL alahdg, alareq, alasum, slarhs, slatb9, slatms,
208  $ slsets
209 * ..
210 * .. Intrinsic Functions ..
211  INTRINSIC abs, max
212 * ..
213 * .. Executable Statements ..
214 *
215 * Initialize constants and the random number seed.
216 *
217  path( 1: 3 ) = 'LSE'
218  info = 0
219  nrun = 0
220  nfail = 0
221  firstt = .true.
222  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
223  lda = nmax
224  ldb = nmax
225  lwork = nmax*nmax
226 *
227 * Check for valid input values.
228 *
229  DO 10 ik = 1, nn
230  m = mval( ik )
231  p = pval( ik )
232  n = nval( ik )
233  IF( p.GT.n .OR. n.GT.m+p ) THEN
234  IF( firstt ) THEN
235  WRITE( nout, fmt = * )
236  firstt = .false.
237  END IF
238  WRITE( nout, fmt = 9997 )m, p, n
239  END IF
240  10 CONTINUE
241  firstt = .true.
242 *
243 * Do for each value of M in MVAL.
244 *
245  DO 40 ik = 1, nn
246  m = mval( ik )
247  p = pval( ik )
248  n = nval( ik )
249  IF( p.GT.n .OR. n.GT.m+p )
250  $ GO TO 40
251 *
252  DO 30 imat = 1, ntypes
253 *
254 * Do the tests only if DOTYPE( IMAT ) is true.
255 *
256  IF( .NOT.dotype( imat ) )
257  $ GO TO 30
258 *
259 * Set up parameters with SLATB9 and generate test
260 * matrices A and B with SLATMS.
261 *
262  CALL slatb9( path, imat, m, p, n, TYPE, KLA, KUA, KLB, KUB,
263  $ anorm, bnorm, modea, modeb, cndnma, cndnmb,
264  $ dista, distb )
265 *
266  CALL slatms( m, n, dista, iseed, TYPE, RWORK, MODEA, CNDNMA,
267  $ anorm, kla, kua, 'No packing', a, lda, work,
268  $ iinfo )
269  IF( iinfo.NE.0 ) THEN
270  WRITE( nout, fmt = 9999 )iinfo
271  info = abs( iinfo )
272  GO TO 30
273  END IF
274 *
275  CALL slatms( p, n, distb, iseed, TYPE, RWORK, MODEB, CNDNMB,
276  $ bnorm, klb, kub, 'No packing', b, ldb, work,
277  $ iinfo )
278  IF( iinfo.NE.0 ) THEN
279  WRITE( nout, fmt = 9999 )iinfo
280  info = abs( iinfo )
281  GO TO 30
282  END IF
283 *
284 * Generate the right-hand sides C and D for the LSE.
285 *
286  CALL slarhs( 'SGE', 'New solution', 'Upper', 'N', m, n,
287  $ max( m-1, 0 ), max( n-1, 0 ), 1, a, lda,
288  $ x( 4*nmax+1 ), max( n, 1 ), x, max( m, 1 ),
289  $ iseed, iinfo )
290 *
291  CALL slarhs( 'SGE', 'Computed', 'Upper', 'N', p, n,
292  $ max( p-1, 0 ), max( n-1, 0 ), 1, b, ldb,
293  $ x( 4*nmax+1 ), max( n, 1 ), x( 2*nmax+1 ),
294  $ max( p, 1 ), iseed, iinfo )
295 *
296  nt = 2
297 *
298  CALL slsets( m, p, n, a, af, lda, b, bf, ldb, x,
299  $ x( nmax+1 ), x( 2*nmax+1 ), x( 3*nmax+1 ),
300  $ x( 4*nmax+1 ), work, lwork, rwork,
301  $ result( 1 ) )
302 *
303 * Print information about the tests that did not
304 * pass the threshold.
305 *
306  DO 20 i = 1, nt
307  IF( result( i ).GE.thresh ) THEN
308  IF( nfail.EQ.0 .AND. firstt ) THEN
309  firstt = .false.
310  CALL alahdg( nout, path )
311  END IF
312  WRITE( nout, fmt = 9998 )m, p, n, imat, i,
313  $ result( i )
314  nfail = nfail + 1
315  END IF
316  20 CONTINUE
317  nrun = nrun + nt
318 *
319  30 CONTINUE
320  40 CONTINUE
321 *
322 * Print a summary of the results.
323 *
324  CALL alasum( path, nout, nfail, nrun, 0 )
325 *
326  9999 FORMAT( ' SLATMS in SCKLSE INFO = ', i5 )
327  9998 FORMAT( ' M=', i4, ' P=', i4, ', N=', i4, ', type ', i2,
328  $ ', test ', i2, ', ratio=', g13.6 )
329  9997 FORMAT( ' *** Invalid input for LSE: M = ', i6, ', P = ', i6,
330  $ ', N = ', i6, ';', / ' must satisfy P <= N <= P+M ',
331  $ '(this set of values will be skipped)' )
332  RETURN
333 *
334 * End of SCKLSE
335 *
336  END
subroutine slarhs(PATH, XTYPE, UPLO, TRANS, M, N, KL, KU, NRHS, A, LDA, X, LDX, B, LDB, ISEED, INFO)
SLARHS
Definition: slarhs.f:206
subroutine slsets(M, P, N, A, AF, LDA, B, BF, LDB, C, CF, D, DF, X, WORK, LWORK, RWORK, RESULT)
SLSETS
Definition: slsets.f:157
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
subroutine slatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
SLATMS
Definition: slatms.f:323
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 scklse(NN, MVAL, PVAL, NVAL, NMATS, ISEED, THRESH, NMAX, A, AF, B, BF, X, WORK, RWORK, NIN, NOUT, INFO)
SCKLSE
Definition: scklse.f:169
subroutine alahdg(IOUNIT, PATH)
ALAHDG
Definition: alahdg.f:64
subroutine alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75