OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
schktr.f
Go to the documentation of this file.
1*> \brief \b SCHKTR
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 SCHKTR( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
12* THRESH, TSTERR, NMAX, A, AINV, B, X, XACT,
13* WORK, RWORK, IWORK, NOUT )
14*
15* .. Scalar Arguments ..
16* LOGICAL TSTERR
17* INTEGER NMAX, NN, NNB, NNS, NOUT
18* REAL THRESH
19* ..
20* .. Array Arguments ..
21* LOGICAL DOTYPE( * )
22* INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
23* REAL A( * ), AINV( * ), B( * ), RWORK( * ),
24* $ WORK( * ), X( * ), XACT( * )
25* ..
26*
27*
28*> \par Purpose:
29* =============
30*>
31*> \verbatim
32*>
33*> SCHKTR tests STRTRI, -TRS, -RFS, and -CON, and SLATRS
34*> \endverbatim
35*
36* Arguments:
37* ==========
38*
39*> \param[in] DOTYPE
40*> \verbatim
41*> DOTYPE is LOGICAL array, dimension (NTYPES)
42*> The matrix types to be used for testing. Matrices of type j
43*> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
44*> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
45*> \endverbatim
46*>
47*> \param[in] NN
48*> \verbatim
49*> NN is INTEGER
50*> The number of values of N contained in the vector NVAL.
51*> \endverbatim
52*>
53*> \param[in] NVAL
54*> \verbatim
55*> NVAL is INTEGER array, dimension (NN)
56*> The values of the matrix column dimension N.
57*> \endverbatim
58*>
59*> \param[in] NNB
60*> \verbatim
61*> NNB is INTEGER
62*> The number of values of NB contained in the vector NBVAL.
63*> \endverbatim
64*>
65*> \param[in] NBVAL
66*> \verbatim
67*> NBVAL is INTEGER array, dimension (NNB)
68*> The values of the blocksize NB.
69*> \endverbatim
70*>
71*> \param[in] NNS
72*> \verbatim
73*> NNS is INTEGER
74*> The number of values of NRHS contained in the vector NSVAL.
75*> \endverbatim
76*>
77*> \param[in] NSVAL
78*> \verbatim
79*> NSVAL is INTEGER array, dimension (NNS)
80*> The values of the number of right hand sides NRHS.
81*> \endverbatim
82*>
83*> \param[in] THRESH
84*> \verbatim
85*> THRESH is REAL
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] TSTERR
92*> \verbatim
93*> TSTERR is LOGICAL
94*> Flag that indicates whether error exits are to be tested.
95*> \endverbatim
96*>
97*> \param[in] NMAX
98*> \verbatim
99*> NMAX is INTEGER
100*> The leading dimension of the work arrays.
101*> NMAX >= the maximum value of N in NVAL.
102*> \endverbatim
103*>
104*> \param[out] A
105*> \verbatim
106*> A is REAL array, dimension (NMAX*NMAX)
107*> \endverbatim
108*>
109*> \param[out] AINV
110*> \verbatim
111*> AINV is REAL array, dimension (NMAX*NMAX)
112*> \endverbatim
113*>
114*> \param[out] B
115*> \verbatim
116*> B is REAL array, dimension (NMAX*NSMAX)
117*> where NSMAX is the largest entry in NSVAL.
118*> \endverbatim
119*>
120*> \param[out] X
121*> \verbatim
122*> X is REAL array, dimension (NMAX*NSMAX)
123*> \endverbatim
124*>
125*> \param[out] XACT
126*> \verbatim
127*> XACT is REAL array, dimension (NMAX*NSMAX)
128*> \endverbatim
129*>
130*> \param[out] WORK
131*> \verbatim
132*> WORK is REAL array, dimension
133*> (NMAX*max(3,NSMAX))
134*> \endverbatim
135*>
136*> \param[out] RWORK
137*> \verbatim
138*> RWORK is REAL array, dimension
139*> (max(NMAX,2*NSMAX))
140*> \endverbatim
141*>
142*> \param[out] IWORK
143*> \verbatim
144*> IWORK is INTEGER array, dimension (NMAX)
145*> \endverbatim
146*>
147*> \param[in] NOUT
148*> \verbatim
149*> NOUT is INTEGER
150*> The unit number for output.
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 single_lin
162*
163* =====================================================================
164 SUBROUTINE schktr( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
165 $ THRESH, TSTERR, NMAX, A, AINV, B, X, XACT,
166 $ WORK, RWORK, IWORK, NOUT )
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 LOGICAL TSTERR
174 INTEGER NMAX, NN, NNB, NNS, NOUT
175 REAL THRESH
176* ..
177* .. Array Arguments ..
178 LOGICAL DOTYPE( * )
179 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
180 REAL A( * ), AINV( * ), B( * ), RWORK( * ),
181 $ work( * ), x( * ), xact( * )
182* ..
183*
184* =====================================================================
185*
186* .. Parameters ..
187 INTEGER NTYPE1, NTYPES
188 PARAMETER ( NTYPE1 = 10, ntypes = 18 )
189 INTEGER NTESTS
190 parameter( ntests = 9 )
191 INTEGER NTRAN
192 parameter( ntran = 3 )
193 REAL ONE, ZERO
194 parameter( one = 1.0e0, zero = 0.0e0 )
195* ..
196* .. Local Scalars ..
197 CHARACTER DIAG, NORM, TRANS, UPLO, XTYPE
198 CHARACTER*3 PATH
199 INTEGER I, IDIAG, IMAT, IN, INB, INFO, IRHS, ITRAN,
200 $ iuplo, k, lda, n, nb, nerrs, nfail, nrhs, nrun
201 REAL AINVNM, ANORM, DUMMY, RCOND, RCONDC, RCONDI,
202 $ RCONDO, SCALE
203* ..
204* .. Local Arrays ..
205 CHARACTER TRANSS( NTRAN ), UPLOS( 2 )
206 INTEGER ISEED( 4 ), ISEEDY( 4 )
207 REAL RESULT( NTESTS )
208* ..
209* .. External Functions ..
210 LOGICAL LSAME
211 REAL SLANTR
212 EXTERNAL lsame, slantr
213* ..
214* .. External Subroutines ..
215 EXTERNAL alaerh, alahd, alasum, scopy, serrtr, sget04,
218 $ strtrs, xlaenv
219* ..
220* .. Scalars in Common ..
221 LOGICAL LERR, OK
222 CHARACTER*32 SRNAMT
223 INTEGER INFOT, IOUNIT
224* ..
225* .. Common blocks ..
226 COMMON / infoc / infot, iounit, ok, lerr
227 COMMON / srnamc / srnamt
228* ..
229* .. Intrinsic Functions ..
230 INTRINSIC max
231* ..
232* .. Data statements ..
233 DATA iseedy / 1988, 1989, 1990, 1991 /
234 DATA uplos / 'U', 'L' / , transs / 'n', 't', 'c' /
235* ..
236* .. Executable Statements ..
237*
238* Initialize constants and the random number seed.
239*
240 PATH( 1: 1 ) = 'single precision'
241 PATH( 2: 3 ) = 'tr'
242 NRUN = 0
243 NFAIL = 0
244 NERRS = 0
245 DO 10 I = 1, 4
246 ISEED( I ) = ISEEDY( I )
247 10 CONTINUE
248*
249* Test the error exits
250*
251 IF( TSTERR )
252 $ CALL SERRTR( PATH, NOUT )
253 INFOT = 0
254 CALL XLAENV( 2, 2 )
255*
256 DO 120 IN = 1, NN
257*
258* Do for each value of N in NVAL
259*
260 N = NVAL( IN )
261 LDA = MAX( 1, N )
262 XTYPE = 'n'
263*
264 DO 80 IMAT = 1, NTYPE1
265*
266* Do the tests only if DOTYPE( IMAT ) is true.
267*
268.NOT. IF( DOTYPE( IMAT ) )
269 $ GO TO 80
270*
271 DO 70 IUPLO = 1, 2
272*
273* Do first for UPLO = 'U', then for UPLO = 'L'
274*
275 UPLO = UPLOS( IUPLO )
276*
277* Call SLATTR to generate a triangular test matrix.
278*
279 SRNAMT = 'slattr'
280 CALL SLATTR( IMAT, UPLO, 'no transpose', DIAG, ISEED, N,
281 $ A, LDA, X, WORK, INFO )
282*
283* Set IDIAG = 1 for non-unit matrices, 2 for unit.
284*
285 IF( LSAME( DIAG, 'n' ) ) THEN
286 IDIAG = 1
287 ELSE
288 IDIAG = 2
289 END IF
290*
291 DO 60 INB = 1, NNB
292*
293* Do for each blocksize in NBVAL
294*
295 NB = NBVAL( INB )
296 CALL XLAENV( 1, NB )
297*
298*+ TEST 1
299* Form the inverse of A.
300*
301 CALL SLACPY( UPLO, N, N, A, LDA, AINV, LDA )
302 SRNAMT = 'strtri'
303 CALL STRTRI( UPLO, DIAG, N, AINV, LDA, INFO )
304*
305* Check error code from STRTRI.
306*
307.NE. IF( INFO0 )
308 $ CALL ALAERH( PATH, 'strtri', INFO, 0, UPLO // DIAG,
309 $ N, N, -1, -1, NB, IMAT, NFAIL, NERRS,
310 $ NOUT )
311*
312* Compute the infinity-norm condition number of A.
313*
314 ANORM = SLANTR( 'i', UPLO, DIAG, N, N, A, LDA, RWORK )
315 AINVNM = SLANTR( 'i', UPLO, DIAG, N, N, AINV, LDA,
316 $ RWORK )
317.LE..OR..LE. IF( ANORMZERO AINVNMZERO ) THEN
318 RCONDI = ONE
319 ELSE
320 RCONDI = ( ONE / ANORM ) / AINVNM
321 END IF
322*
323* Compute the residual for the triangular matrix times
324* its inverse. Also compute the 1-norm condition number
325* of A.
326*
327 CALL STRT01( UPLO, DIAG, N, A, LDA, AINV, LDA, RCONDO,
328 $ RWORK, RESULT( 1 ) )
329*
330* Print the test ratio if it is .GE. THRESH.
331*
332.GE. IF( RESULT( 1 )THRESH ) THEN
333.EQ..AND..EQ. IF( NFAIL0 NERRS0 )
334 $ CALL ALAHD( NOUT, PATH )
335 WRITE( NOUT, FMT = 9999 )UPLO, DIAG, N, NB, IMAT,
336 $ 1, RESULT( 1 )
337 NFAIL = NFAIL + 1
338 END IF
339 NRUN = NRUN + 1
340*
341* Skip remaining tests if not the first block size.
342*
343.NE. IF( INB1 )
344 $ GO TO 60
345*
346 DO 40 IRHS = 1, NNS
347 NRHS = NSVAL( IRHS )
348 XTYPE = 'n'
349*
350 DO 30 ITRAN = 1, NTRAN
351*
352* Do for op(A) = A, A**T, or A**H.
353*
354 TRANS = TRANSS( ITRAN )
355.EQ. IF( ITRAN1 ) THEN
356 NORM = 'o'
357 RCONDC = RCONDO
358 ELSE
359 NORM = 'i'
360 RCONDC = RCONDI
361 END IF
362*
363*+ TEST 2
364* Solve and compute residual for op(A)*x = b.
365*
366 SRNAMT = 'slarhs'
367 CALL SLARHS( PATH, XTYPE, UPLO, TRANS, N, N, 0,
368 $ IDIAG, NRHS, A, LDA, XACT, LDA, B,
369 $ LDA, ISEED, INFO )
370 XTYPE = 'c'
371 CALL SLACPY( 'full', N, NRHS, B, LDA, X, LDA )
372*
373 SRNAMT = 'strtrs'
374 CALL STRTRS( UPLO, TRANS, DIAG, N, NRHS, A, LDA,
375 $ X, LDA, INFO )
376*
377* Check error code from STRTRS.
378*
379.NE. IF( INFO0 )
380 $ CALL ALAERH( PATH, 'strtrs', INFO, 0,
381 $ UPLO // TRANS // DIAG, N, N, -1,
382 $ -1, NRHS, IMAT, NFAIL, NERRS,
383 $ NOUT )
384*
385* This line is needed on a Sun SPARCstation.
386*
387.GT. IF( N0 )
388 $ DUMMY = A( 1 )
389*
390 CALL STRT02( UPLO, TRANS, DIAG, N, NRHS, A, LDA,
391 $ X, LDA, B, LDA, WORK, RESULT( 2 ) )
392*
393*+ TEST 3
394* Check solution from generated exact solution.
395*
396 CALL SGET04( N, NRHS, X, LDA, XACT, LDA, RCONDC,
397 $ RESULT( 3 ) )
398*
399*+ TESTS 4, 5, and 6
400* Use iterative refinement to improve the solution
401* and compute error bounds.
402*
403 SRNAMT = 'strrfs'
404 CALL STRRFS( UPLO, TRANS, DIAG, N, NRHS, A, LDA,
405 $ B, LDA, X, LDA, RWORK,
406 $ RWORK( NRHS+1 ), WORK, IWORK,
407 $ INFO )
408*
409* Check error code from STRRFS.
410*
411.NE. IF( INFO0 )
412 $ CALL ALAERH( PATH, 'strrfs', INFO, 0,
413 $ UPLO // TRANS // DIAG, N, N, -1,
414 $ -1, NRHS, IMAT, NFAIL, NERRS,
415 $ NOUT )
416*
417 CALL SGET04( N, NRHS, X, LDA, XACT, LDA, RCONDC,
418 $ RESULT( 4 ) )
419 CALL STRT05( UPLO, TRANS, DIAG, N, NRHS, A, LDA,
420 $ B, LDA, X, LDA, XACT, LDA, RWORK,
421 $ RWORK( NRHS+1 ), RESULT( 5 ) )
422*
423* Print information about the tests that did not
424* pass the threshold.
425*
426 DO 20 K = 2, 6
427.GE. IF( RESULT( K )THRESH ) THEN
428.EQ..AND..EQ. IF( NFAIL0 NERRS0 )
429 $ CALL ALAHD( NOUT, PATH )
430 WRITE( NOUT, FMT = 9998 )UPLO, TRANS,
431 $ DIAG, N, NRHS, IMAT, K, RESULT( K )
432 NFAIL = NFAIL + 1
433 END IF
434 20 CONTINUE
435 NRUN = NRUN + 5
436 30 CONTINUE
437 40 CONTINUE
438*
439*+ TEST 7
440* Get an estimate of RCOND = 1/CNDNUM.
441*
442 DO 50 ITRAN = 1, 2
443.EQ. IF( ITRAN1 ) THEN
444 NORM = 'o'
445 RCONDC = RCONDO
446 ELSE
447 NORM = 'i'
448 RCONDC = RCONDI
449 END IF
450 SRNAMT = 'strcon'
451 CALL STRCON( NORM, UPLO, DIAG, N, A, LDA, RCOND,
452 $ WORK, IWORK, INFO )
453*
454* Check error code from STRCON.
455*
456.NE. IF( INFO0 )
457 $ CALL ALAERH( PATH, 'strcon', INFO, 0,
458 $ NORM // UPLO // DIAG, N, N, -1, -1,
459 $ -1, IMAT, NFAIL, NERRS, NOUT )
460*
461 CALL STRT06( RCOND, RCONDC, UPLO, DIAG, N, A, LDA,
462 $ RWORK, RESULT( 7 ) )
463*
464* Print the test ratio if it is .GE. THRESH.
465*
466.GE. IF( RESULT( 7 )THRESH ) THEN
467.EQ..AND..EQ. IF( NFAIL0 NERRS0 )
468 $ CALL ALAHD( NOUT, PATH )
469 WRITE( NOUT, FMT = 9997 )NORM, UPLO, N, IMAT,
470 $ 7, RESULT( 7 )
471 NFAIL = NFAIL + 1
472 END IF
473 NRUN = NRUN + 1
474 50 CONTINUE
475 60 CONTINUE
476 70 CONTINUE
477 80 CONTINUE
478*
479* Use pathological test matrices to test SLATRS.
480*
481 DO 110 IMAT = NTYPE1 + 1, NTYPES
482*
483* Do the tests only if DOTYPE( IMAT ) is true.
484*
485.NOT. IF( DOTYPE( IMAT ) )
486 $ GO TO 110
487*
488 DO 100 IUPLO = 1, 2
489*
490* Do first for UPLO = 'U', then for UPLO = 'L'
491*
492 UPLO = UPLOS( IUPLO )
493 DO 90 ITRAN = 1, NTRAN
494*
495* Do for op(A) = A, A**T, and A**H.
496*
497 TRANS = TRANSS( ITRAN )
498*
499* Call SLATTR to generate a triangular test matrix.
500*
501 SRNAMT = 'slattr'
502 CALL SLATTR( IMAT, UPLO, TRANS, DIAG, ISEED, N, A,
503 $ LDA, X, WORK, INFO )
504*
505*+ TEST 8
506* Solve the system op(A)*x = b.
507*
508 SRNAMT = 'slatrs'
509 CALL SCOPY( N, X, 1, B, 1 )
510 CALL SLATRS( UPLO, TRANS, DIAG, 'n', n, a, lda, b,
511 $ scale, rwork, info )
512*
513* Check error code from SLATRS.
514*
515 IF( info.NE.0 )
516 $ CALL alaerh( path, 'SLATRS', info, 0,
517 $ uplo // trans // diag // 'N', n, n,
518 $ -1, -1, -1, imat, nfail, nerrs, nout )
519*
520 CALL strt03( uplo, trans, diag, n, 1, a, lda, scale,
521 $ rwork, one, b, lda, x, lda, work,
522 $ result( 8 ) )
523*
524*+ TEST 9
525* Solve op(A)*X = b again with NORMIN = 'Y'.
526*
527 CALL scopy( n, x, 1, b( n+1 ), 1 )
528 CALL slatrs( uplo, trans, diag, 'Y', n, a, lda,
529 $ b( n+1 ), scale, rwork, info )
530*
531* Check error code from SLATRS.
532*
533 IF( info.NE.0 )
534 $ CALL alaerh( path, 'SLATRS', info, 0,
535 $ uplo // trans // diag // 'Y', n, n,
536 $ -1, -1, -1, imat, nfail, nerrs, nout )
537*
538 CALL strt03( uplo, trans, diag, n, 1, a, lda, scale,
539 $ rwork, one, b( n+1 ), lda, x, lda, work,
540 $ result( 9 ) )
541*
542* Print information about the tests that did not pass
543* the threshold.
544*
545 IF( result( 8 ).GE.thresh ) THEN
546 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
547 $ CALL alahd( nout, path )
548 WRITE( nout, fmt = 9996 )'SLATRS', uplo, trans,
549 $ diag, 'N', n, imat, 8, result( 8 )
550 nfail = nfail + 1
551 END IF
552 IF( result( 9 ).GE.thresh ) THEN
553 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
554 $ CALL alahd( nout, path )
555 WRITE( nout, fmt = 9996 )'SLATRS', uplo, trans,
556 $ diag, 'Y', n, imat, 9, result( 9 )
557 nfail = nfail + 1
558 END IF
559 nrun = nrun + 2
560 90 CONTINUE
561 100 CONTINUE
562 110 CONTINUE
563 120 CONTINUE
564*
565* Print a summary of the results.
566*
567 CALL alasum( path, nout, nfail, nrun, nerrs )
568*
569 9999 FORMAT( ' UPLO=''', a1, ''', DIAG=''', a1, ''', N=', i5, ', NB=',
570 $ i4, ', type ', i2, ', test(', i2, ')= ', g12.5 )
571 9998 FORMAT( ' UPLO=''', a1, ''', TRANS=''', a1, ''', DIAG=''', a1,
572 $ ''', N=', i5, ', NB=', i4, ', type ', i2, ',
573 $ test(', i2, ')= ', g12.5 )
574 9997 FORMAT( ' NORM=''', a1, ''', UPLO =''', a1, ''', N=', i5, ',',
575 $ 11x, ' type ', i2, ', test(', i2, ')=', g12.5 )
576 9996 FORMAT( 1x, a, '( ''', a1, ''', ''', a1, ''', ''', a1, ''', ''',
577 $ a1, ''',', i5, ', ... ), type ', i2, ', test(', i2, ')=',
578 $ g12.5 )
579 RETURN
580*
581* End of SCHKTR
582*
583 END
subroutine slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
Definition slacpy.f:103
subroutine xlaenv(ispec, nvalue)
XLAENV
Definition xlaenv.f:81
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
Definition alasum.f:73
subroutine alahd(iounit, path)
ALAHD
Definition alahd.f:107
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
Definition alaerh.f:147
subroutine slatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
SLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition slatrs.f:238
subroutine strtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
STRTRS
Definition strtrs.f:140
subroutine strtri(uplo, diag, n, a, lda, info)
STRTRI
Definition strtri.f:109
subroutine strcon(norm, uplo, diag, n, a, lda, rcond, work, iwork, info)
STRCON
Definition strcon.f:137
subroutine strrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, iwork, info)
STRRFS
Definition strrfs.f:182
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
Definition scopy.f:82
subroutine slarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
SLARHS
Definition slarhs.f:205
subroutine slattr(imat, uplo, trans, diag, iseed, n, a, lda, b, work, info)
SLATTR
Definition slattr.f:133
subroutine strt01(uplo, diag, n, a, lda, ainv, ldainv, rcond, work, resid)
STRT01
Definition strt01.f:124
subroutine strt02(uplo, trans, diag, n, nrhs, a, lda, x, ldx, b, ldb, work, resid)
STRT02
Definition strt02.f:150
subroutine strt05(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
STRT05
Definition strt05.f:181
subroutine strt03(uplo, trans, diag, n, nrhs, a, lda, scale, cnorm, tscal, x, ldx, b, ldb, work, resid)
STRT03
Definition strt03.f:169
subroutine sget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
SGET04
Definition sget04.f:102
subroutine strt06(rcond, rcondc, uplo, diag, n, a, lda, work, rat)
STRT06
Definition strt06.f:121
subroutine serrtr(path, nunit)
SERRTR
Definition serrtr.f:55
subroutine schktr(dotype, nn, nval, nnb, nbval, nns, nsval, thresh, tsterr, nmax, a, ainv, b, x, xact, work, rwork, iwork, nout)
SCHKTR
Definition schktr.f:167
#define max(a, b)
Definition macros.h:21