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

◆ dcklse()

subroutine dcklse ( 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 
)

DCKLSE

Purpose:
 DCKLSE tests DGGLSE - a subroutine for solving linear equality
 constrained least square problem (LSE).
Parameters
[in]NN
          NN is INTEGER
          The number of values of (M,P,N) contained in the vectors
          (MVAL, PVAL, NVAL).
[in]MVAL
          MVAL is INTEGER array, dimension (NN)
          The values of the matrix row(column) dimension M.
[in]PVAL
          PVAL is INTEGER array, dimension (NN)
          The values of the matrix row(column) dimension P.
[in]NVAL
          NVAL is INTEGER array, dimension (NN)
          The values of the matrix column(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 RESULT >= 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 (5*NMAX)
[out]WORK
          WORK is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (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 dcklse.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 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*
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 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
Here is the call graph for this function:
Here is the caller graph for this function: