LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dcklse.f
Go to the documentation of this file.
1*> \brief \b DCKLSE
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 DCKLSE( 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* DOUBLE PRECISION THRESH
18* ..
19* .. Array Arguments ..
20* INTEGER ISEED( 4 ), MVAL( * ), NVAL( * ), PVAL( * )
21* DOUBLE PRECISION A( * ), AF( * ), B( * ), BF( * ), RWORK( * ),
22* $ WORK( * ), X( * )
23* ..
24*
25*
26*> \par Purpose:
27* =============
28*>
29*> \verbatim
30*>
31*> DCKLSE tests DGGLSE - 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 DOUBLE PRECISION
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 DOUBLE PRECISION array, dimension (NMAX*NMAX)
101*> \endverbatim
102*>
103*> \param[out] AF
104*> \verbatim
105*> AF is DOUBLE PRECISION array, dimension (NMAX*NMAX)
106*> \endverbatim
107*>
108*> \param[out] B
109*> \verbatim
110*> B is DOUBLE PRECISION array, dimension (NMAX*NMAX)
111*> \endverbatim
112*>
113*> \param[out] BF
114*> \verbatim
115*> BF is DOUBLE PRECISION array, dimension (NMAX*NMAX)
116*> \endverbatim
117*>
118*> \param[out] X
119*> \verbatim
120*> X is DOUBLE PRECISION array, dimension (5*NMAX)
121*> \endverbatim
122*>
123*> \param[out] WORK
124*> \verbatim
125*> WORK is DOUBLE PRECISION array, dimension (NMAX*NMAX)
126*> \endverbatim
127*>
128*> \param[out] RWORK
129*> \verbatim
130*> RWORK is DOUBLE PRECISION 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 DLATMS 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*> \ingroup double_eig
162*
163* =====================================================================
164 SUBROUTINE dcklse( NN, MVAL, PVAL, NVAL, NMATS, ISEED, THRESH,
165 $ NMAX, A, AF, B, BF, X, WORK, RWORK, NIN, NOUT,
166 $ INFO )
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 NTESTS
186 PARAMETER ( NTESTS = 7 )
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,
196 $ nt, p
197 DOUBLE PRECISION ANORM, BNORM, CNDNMA, CNDNMB
198* ..
199* .. Local Arrays ..
200 LOGICAL DOTYPE( NTYPES )
201 DOUBLE PRECISION RESULT( NTESTS )
202* ..
203* .. External Subroutines ..
204 EXTERNAL alahdg, alareq, alasum, dlarhs, dlatb9, dlatms,
205 $ dlsets
206* ..
207* .. Intrinsic Functions ..
208 INTRINSIC abs, max
209* ..
210* .. Executable Statements ..
211*
212* Initialize constants and the random number seed.
213*
214 path( 1: 3 ) = 'LSE'
215 info = 0
216 nrun = 0
217 nfail = 0
218 firstt = .true.
219 CALL alareq( path, nmats, dotype, ntypes, nin, nout )
220 lda = nmax
221 ldb = nmax
222 lwork = nmax*nmax
223*
224* Check for valid input values.
225*
226 DO 10 ik = 1, nn
227 m = mval( ik )
228 p = pval( ik )
229 n = nval( ik )
230 IF( p.GT.n .OR. n.GT.m+p ) THEN
231 IF( firstt ) THEN
232 WRITE( nout, fmt = * )
233 firstt = .false.
234 END IF
235 WRITE( nout, fmt = 9997 )m, p, n
236 END IF
237 10 CONTINUE
238 firstt = .true.
239*
240* Do for each value of M in MVAL.
241*
242 DO 40 ik = 1, nn
243 m = mval( ik )
244 p = pval( ik )
245 n = nval( ik )
246 IF( p.GT.n .OR. n.GT.m+p )
247 $ GO TO 40
248*
249 DO 30 imat = 1, ntypes
250*
251* Do the tests only if DOTYPE( IMAT ) is true.
252*
253 IF( .NOT.dotype( imat ) )
254 $ GO TO 30
255*
256* Set up parameters with DLATB9 and generate test
257* matrices A and B with DLATMS.
258*
259 CALL dlatb9( path, imat, m, p, n, TYPE, kla, kua, klb, kub,
260 $ anorm, bnorm, modea, modeb, cndnma, cndnmb,
261 $ dista, distb )
262*
263 CALL dlatms( m, n, dista, iseed, TYPE, rwork, modea, cndnma,
264 $ anorm, kla, kua, 'No packing', a, lda, work,
265 $ iinfo )
266 IF( iinfo.NE.0 ) THEN
267 WRITE( nout, fmt = 9999 )iinfo
268 info = abs( iinfo )
269 GO TO 30
270 END IF
271*
272 CALL dlatms( p, n, distb, iseed, TYPE, rwork, modeb, cndnmb,
273 $ bnorm, klb, kub, 'No packing', b, ldb, work,
274 $ iinfo )
275 IF( iinfo.NE.0 ) THEN
276 WRITE( nout, fmt = 9999 )iinfo
277 info = abs( iinfo )
278 GO TO 30
279 END IF
280*
281* Generate the right-hand sides C and D for the LSE.
282*
283 CALL dlarhs( 'DGE', 'New solution', 'Upper', 'N', m, n,
284 $ max( m-1, 0 ), max( n-1, 0 ), 1, a, lda,
285 $ x( 4*nmax+1 ), max( n, 1 ), x, max( m, 1 ),
286 $ iseed, iinfo )
287*
288 CALL dlarhs( 'DGE', 'Computed', 'Upper', 'N', p, n,
289 $ max( p-1, 0 ), max( n-1, 0 ), 1, b, ldb,
290 $ x( 4*nmax+1 ), max( n, 1 ), x( 2*nmax+1 ),
291 $ max( p, 1 ), iseed, iinfo )
292*
293 nt = 2
294*
295 CALL dlsets( m, p, n, a, af, lda, b, bf, ldb, x,
296 $ x( nmax+1 ), x( 2*nmax+1 ), x( 3*nmax+1 ),
297 $ x( 4*nmax+1 ), work, lwork, rwork,
298 $ result( 1 ) )
299*
300* Print information about the tests that did not
301* pass the threshold.
302*
303 DO 20 i = 1, nt
304 IF( result( i ).GE.thresh ) THEN
305 IF( nfail.EQ.0 .AND. firstt ) THEN
306 firstt = .false.
307 CALL alahdg( nout, path )
308 END IF
309 WRITE( nout, fmt = 9998 )m, p, n, imat, i,
310 $ result( i )
311 nfail = nfail + 1
312 END IF
313 20 CONTINUE
314 nrun = nrun + nt
315*
316 30 CONTINUE
317 40 CONTINUE
318*
319* Print a summary of the results.
320*
321 CALL alasum( path, nout, nfail, nrun, 0 )
322*
323 9999 FORMAT( ' DLATMS in DCKLSE INFO = ', i5 )
324 9998 FORMAT( ' M=', i4, ' P=', i4, ', N=', i4, ', type ', i2,
325 $ ', test ', i2, ', ratio=', g13.6 )
326 9997 FORMAT( ' *** Invalid input for LSE: M = ', i6, ', P = ', i6,
327 $ ', N = ', i6, ';', / ' must satisfy P <= N <= P+M ',
328 $ '(this set of values will be skipped)' )
329 RETURN
330*
331* End of DCKLSE
332*
333 END
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 dlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
DLARHS
Definition dlarhs.f:205
subroutine alahdg(iounit, path)
ALAHDG
Definition alahdg.f:62
subroutine dcklse(nn, mval, pval, nval, nmats, iseed, thresh, nmax, a, af, b, bf, x, work, rwork, nin, nout, info)
DCKLSE
Definition dcklse.f:167
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
subroutine dlsets(m, p, n, a, af, lda, b, bf, ldb, c, cf, d, df, x, work, lwork, rwork, result)
DLSETS
Definition dlsets.f:151