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

SCKLSE

Purpose:
 SCKLSE tests SGGLSE - 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 REAL
          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 REAL array, dimension (NMAX*NMAX)
[out]AF
          AF is REAL array, dimension (NMAX*NMAX)
[out]B
          B is REAL array, dimension (NMAX*NMAX)
[out]BF
          BF is REAL array, dimension (NMAX*NMAX)
[out]X
          X is REAL array, dimension (5*NMAX)
[out]WORK
          WORK is REAL array, dimension (NMAX*NMAX)
[out]RWORK
          RWORK is REAL 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 SLATMS 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 169 of file scklse.f.

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 *
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 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: