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

◆ zcklse()

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.

Definition at line 165 of file zcklse.f.

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