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

ZCKLSE

Purpose:
 ZCKLSE tests ZGGLSE - 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 COMPLEX*16 array, dimension (NMAX*NMAX)
[out]AF
          AF is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]B
          B is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]BF
          BF is COMPLEX*16 array, dimension (NMAX*NMAX)
[out]X
          X is COMPLEX*16 array, dimension (5*NMAX)
[out]WORK
          WORK is COMPLEX*16 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 ZLATMS 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 170 of file zcklse.f.

170 *
171 * -- LAPACK test routine (version 3.4.0) --
172 * -- LAPACK is a software package provided by Univ. of Tennessee, --
173 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
174 * November 2011
175 *
176 * .. Scalar Arguments ..
177  INTEGER info, nin, nmats, nmax, nn, nout
178  DOUBLE PRECISION thresh
179 * ..
180 * .. Array Arguments ..
181  INTEGER iseed( 4 ), mval( * ), nval( * ), pval( * )
182  DOUBLE PRECISION rwork( * )
183  COMPLEX*16 a( * ), af( * ), b( * ), bf( * ), work( * ),
184  $ x( * )
185 * ..
186 *
187 * =====================================================================
188 *
189 * .. Parameters ..
190  INTEGER ntests
191  parameter ( ntests = 7 )
192  INTEGER ntypes
193  parameter ( ntypes = 8 )
194 * ..
195 * .. Local Scalars ..
196  LOGICAL firstt
197  CHARACTER dista, distb, type
198  CHARACTER*3 path
199  INTEGER i, iinfo, ik, imat, kla, klb, kua, kub, lda,
200  $ ldb, lwork, m, modea, modeb, n, nfail, nrun,
201  $ nt, p
202  DOUBLE PRECISION anorm, bnorm, cndnma, cndnmb
203 * ..
204 * .. Local Arrays ..
205  LOGICAL dotype( ntypes )
206  DOUBLE PRECISION result( ntests )
207 * ..
208 * .. External Subroutines ..
209  EXTERNAL alahdg, alareq, alasum, dlatb9, zlarhs, zlatms,
210  $ zlsets
211 * ..
212 * .. Intrinsic Functions ..
213  INTRINSIC abs, max
214 * ..
215 * .. Executable Statements ..
216 *
217 * Initialize constants and the random number seed.
218 *
219  path( 1: 3 ) = 'LSE'
220  info = 0
221  nrun = 0
222  nfail = 0
223  firstt = .true.
224  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
225  lda = nmax
226  ldb = nmax
227  lwork = nmax*nmax
228 *
229 * Check for valid input values.
230 *
231  DO 10 ik = 1, nn
232  m = mval( ik )
233  p = pval( ik )
234  n = nval( ik )
235  IF( p.GT.n .OR. n.GT.m+p ) THEN
236  IF( firstt ) THEN
237  WRITE( nout, fmt = * )
238  firstt = .false.
239  END IF
240  WRITE( nout, fmt = 9997 )m, p, n
241  END IF
242  10 CONTINUE
243  firstt = .true.
244 *
245 * Do for each value of M in MVAL.
246 *
247  DO 40 ik = 1, nn
248  m = mval( ik )
249  p = pval( ik )
250  n = nval( ik )
251  IF( p.GT.n .OR. n.GT.m+p )
252  $ GO TO 40
253 *
254  DO 30 imat = 1, ntypes
255 *
256 * Do the tests only if DOTYPE( IMAT ) is true.
257 *
258  IF( .NOT.dotype( imat ) )
259  $ GO TO 30
260 *
261 * Set up parameters with DLATB9 and generate test
262 * matrices A and B with ZLATMS.
263 *
264  CALL dlatb9( path, imat, m, p, n, TYPE, kla, kua, klb, kub,
265  $ anorm, bnorm, modea, modeb, cndnma, cndnmb,
266  $ dista, distb )
267 *
268  CALL zlatms( m, n, dista, iseed, TYPE, rwork, modea, cndnma,
269  $ anorm, kla, kua, 'No packing', a, lda, work,
270  $ iinfo )
271  IF( iinfo.NE.0 ) THEN
272  WRITE( nout, fmt = 9999 )iinfo
273  info = abs( iinfo )
274  GO TO 30
275  END IF
276 *
277  CALL zlatms( p, n, distb, iseed, TYPE, rwork, modeb, cndnmb,
278  $ bnorm, klb, kub, 'No packing', b, ldb, work,
279  $ iinfo )
280  IF( iinfo.NE.0 ) THEN
281  WRITE( nout, fmt = 9999 )iinfo
282  info = abs( iinfo )
283  GO TO 30
284  END IF
285 *
286 * Generate the right-hand sides C and D for the LSE.
287 *
288  CALL zlarhs( 'ZGE', 'New solution', 'Upper', 'N', m, n,
289  $ max( m-1, 0 ), max( n-1, 0 ), 1, a, lda,
290  $ x( 4*nmax+1 ), max( n, 1 ), x, max( m, 1 ),
291  $ iseed, iinfo )
292 *
293  CALL zlarhs( 'ZGE', 'Computed', 'Upper', 'N', p, n,
294  $ max( p-1, 0 ), max( n-1, 0 ), 1, b, ldb,
295  $ x( 4*nmax+1 ), max( n, 1 ), x( 2*nmax+1 ),
296  $ max( p, 1 ), iseed, iinfo )
297 *
298  nt = 2
299 *
300  CALL zlsets( m, p, n, a, af, lda, b, bf, ldb, x,
301  $ x( nmax+1 ), x( 2*nmax+1 ), x( 3*nmax+1 ),
302  $ x( 4*nmax+1 ), work, lwork, rwork,
303  $ result( 1 ) )
304 *
305 * Print information about the tests that did not
306 * pass the threshold.
307 *
308  DO 20 i = 1, nt
309  IF( result( i ).GE.thresh ) THEN
310  IF( nfail.EQ.0 .AND. firstt ) THEN
311  firstt = .false.
312  CALL alahdg( nout, path )
313  END IF
314  WRITE( nout, fmt = 9998 )m, p, n, imat, i,
315  $ result( i )
316  nfail = nfail + 1
317  END IF
318  20 CONTINUE
319  nrun = nrun + nt
320 *
321  30 CONTINUE
322  40 CONTINUE
323 *
324 * Print a summary of the results.
325 *
326  CALL alasum( path, nout, nfail, nrun, 0 )
327 *
328  9999 FORMAT( ' ZLATMS in ZCKLSE INFO = ', i5 )
329  9998 FORMAT( ' M=', i4, ' P=', i4, ', N=', i4, ', type ', i2,
330  $ ', test ', i2, ', ratio=', g13.6 )
331  9997 FORMAT( ' *** Invalid input for LSE: M = ', i6, ', P = ', i6,
332  $ ', N = ', i6, ';', / ' must satisfy P <= N <= P+M ',
333  $ '(this set of values will be skipped)' )
334  RETURN
335 *
336 * End of ZCKLSE
337 *
subroutine zlarhs(PATH, XTYPE, UPLO, TRANS, M, N, KL, KU, NRHS, A, LDA, X, LDX, B, LDB, ISEED, INFO)
ZLARHS
Definition: zlarhs.f:211
subroutine alareq(PATH, NMATS, DOTYPE, NTYPES, NIN, NOUT)
ALAREQ
Definition: alareq.f:92
subroutine dlatb9(PATH, IMAT, M, P, N, TYPE, KLA, KUA, KLB, KUB, ANORM, BNORM, MODEA, MODEB, CNDNMA, CNDNMB, DISTA, DISTB)
DLATB9
Definition: dlatb9.f:172
subroutine zlsets(M, P, N, A, AF, LDA, B, BF, LDB, C, CF, D, DF, X, WORK, LWORK, RWORK, RESULT)
ZLSETS
Definition: zlsets.f:153
subroutine zlatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
ZLATMS
Definition: zlatms.f:334
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: