aboutsummaryrefslogtreecommitdiff
path: root/INSTALL
diff options
context:
space:
mode:
authorjason <jason@8a072113-8704-0410-8d35-dd094bca7971>2008-10-28 01:38:50 +0000
committerjason <jason@8a072113-8704-0410-8d35-dd094bca7971>2008-10-28 01:38:50 +0000
commitbaba851215b44ac3b60b9248eb02bcce7eb76247 (patch)
tree8c0f5c006875532a30d4409f5e94b0f310ff00a7 /INSTALL
Move LAPACK trunk into position.
Diffstat (limited to 'INSTALL')
-rw-r--r--INSTALL/LAPACK_version.f12
-rw-r--r--INSTALL/Makefile35
-rw-r--r--INSTALL/dlamch.f852
-rw-r--r--INSTALL/dlamchtst.f40
-rw-r--r--INSTALL/dsecnd_EXT_ETIME.f33
-rw-r--r--INSTALL/dsecnd_EXT_ETIME_.f33
-rw-r--r--INSTALL/dsecnd_INT_CPU_TIME.f31
-rw-r--r--INSTALL/dsecnd_INT_ETIME.f33
-rw-r--r--INSTALL/dsecnd_NONE.f22
-rw-r--r--INSTALL/dsecndtst.f91
-rw-r--r--INSTALL/ilaver.f34
-rw-r--r--INSTALL/lawn81.tex1656
-rw-r--r--INSTALL/lpk_gnumake.tarbin0 -> 133120 bytes
-rw-r--r--INSTALL/lsame.f86
-rw-r--r--INSTALL/lsametst.f60
-rw-r--r--INSTALL/make.inc.ALPHA69
-rw-r--r--INSTALL/make.inc.HPPA69
-rw-r--r--INSTALL/make.inc.IRIX6472
-rw-r--r--INSTALL/make.inc.LINUX68
-rw-r--r--INSTALL/make.inc.O2K74
-rw-r--r--INSTALL/make.inc.RS6K69
-rw-r--r--INSTALL/make.inc.SGI569
-rw-r--r--INSTALL/make.inc.SUN469
-rw-r--r--INSTALL/make.inc.SUN4SOL275
-rw-r--r--INSTALL/make.inc.gfortran68
-rw-r--r--INSTALL/make.inc.pghpf69
-rw-r--r--INSTALL/org2.ps768
-rw-r--r--INSTALL/psfig.tex391
-rw-r--r--INSTALL/second_EXT_ETIME.f33
-rw-r--r--INSTALL/second_EXT_ETIME_.f33
-rw-r--r--INSTALL/second_INT_CPU_TIME.f31
-rw-r--r--INSTALL/second_INT_ETIME.f33
-rw-r--r--INSTALL/second_NONE.f22
-rw-r--r--INSTALL/secondtst.f91
-rw-r--r--INSTALL/slamch.f853
-rw-r--r--INSTALL/slamchtst.f40
-rw-r--r--INSTALL/tstiee.f750
37 files changed, 6834 insertions, 0 deletions
diff --git a/INSTALL/LAPACK_version.f b/INSTALL/LAPACK_version.f
new file mode 100644
index 00000000..c70ead5f
--- /dev/null
+++ b/INSTALL/LAPACK_version.f
@@ -0,0 +1,12 @@
+
+ PROGRAM LAPACK_VERSION
+*
+*
+*
+ INTEGER MAJOR, MINOR, PATCH
+*
+ CALL ILAVER ( MAJOR,MINOR, PATCH )
+
+ WRITE(*,*) "LAPACK ",MAJOR,".",MINOR,".",PATCH
+*
+ END
diff --git a/INSTALL/Makefile b/INSTALL/Makefile
new file mode 100644
index 00000000..a6501c30
--- /dev/null
+++ b/INSTALL/Makefile
@@ -0,0 +1,35 @@
+include ../make.inc
+
+.SUFFIXES : .o .f
+all: testlsame testslamch testdlamch testsecond testdsecnd testieee testversion
+
+testlsame: lsame.o lsametst.o
+ $(LOADER) $(LOADOPTS) -o testlsame lsame.o lsametst.o
+
+testslamch: slamch.o lsame.o slamchtst.o
+ $(LOADER) $(LOADOPTS) -o testslamch slamch.o lsame.o slamchtst.o
+
+testdlamch: dlamch.o lsame.o dlamchtst.o
+ $(LOADER) $(LOADOPTS) -o testdlamch dlamch.o lsame.o dlamchtst.o
+
+testsecond: second_$(TIMER).o secondtst.o
+ @echo "[INFO] : TIMER value: $(TIMER) (given by make.inc)"
+ $(LOADER) $(LOADOPTS) -o testsecond second_$(TIMER).o secondtst.o
+
+testdsecnd: dsecnd_$(TIMER).o dsecndtst.o
+ @echo "[INFO] : TIMER value: $(TIMER) (given by make.inc)"
+ $(LOADER) $(LOADOPTS) -o testdsecnd dsecnd_$(TIMER).o dsecndtst.o
+
+testieee: tstiee.o
+ $(LOADER) $(LOADOPTS) -o testieee tstiee.o
+
+testversion: ilaver.o LAPACK_version.o
+ $(LOADER) $(LOADOPTS) -o testversion ilaver.o LAPACK_version.o
+
+clean:
+ rm -f *.o
+
+slamch.o: slamch.f ; $(FORTRAN) $(NOOPT) -c $< -o $@
+dlamch.o: dlamch.f ; $(FORTRAN) $(NOOPT) -c $< -o $@
+
+.f.o: ; $(FORTRAN) $(OPTS) -c $< -o $@
diff --git a/INSTALL/dlamch.f b/INSTALL/dlamch.f
new file mode 100644
index 00000000..1664fab1
--- /dev/null
+++ b/INSTALL/dlamch.f
@@ -0,0 +1,852 @@
+ DOUBLE PRECISION FUNCTION DLAMCH( CMACH )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ CHARACTER CMACH
+* ..
+*
+* Purpose
+* =======
+*
+* DLAMCH determines double precision machine parameters.
+*
+* Arguments
+* =========
+*
+* CMACH (input) CHARACTER*1
+* Specifies the value to be returned by DLAMCH:
+* = 'E' or 'e', DLAMCH := eps
+* = 'S' or 's , DLAMCH := sfmin
+* = 'B' or 'b', DLAMCH := base
+* = 'P' or 'p', DLAMCH := eps*base
+* = 'N' or 'n', DLAMCH := t
+* = 'R' or 'r', DLAMCH := rnd
+* = 'M' or 'm', DLAMCH := emin
+* = 'U' or 'u', DLAMCH := rmin
+* = 'L' or 'l', DLAMCH := emax
+* = 'O' or 'o', DLAMCH := rmax
+*
+* where
+*
+* eps = relative machine precision
+* sfmin = safe minimum, such that 1/sfmin does not overflow
+* base = base of the machine
+* prec = eps*base
+* t = number of (base) digits in the mantissa
+* rnd = 1.0 when rounding occurs in addition, 0.0 otherwise
+* emin = minimum exponent before (gradual) underflow
+* rmin = underflow threshold - base**(emin-1)
+* emax = largest exponent before overflow
+* rmax = overflow threshold - (base**emax)*(1-eps)
+*
+* =====================================================================
+*
+* .. Parameters ..
+ DOUBLE PRECISION ONE, ZERO
+ PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
+* ..
+* .. Local Scalars ..
+ LOGICAL FIRST, LRND
+ INTEGER BETA, IMAX, IMIN, IT
+ DOUBLE PRECISION BASE, EMAX, EMIN, EPS, PREC, RMACH, RMAX, RMIN,
+ $ RND, SFMIN, SMALL, T
+* ..
+* .. External Functions ..
+ LOGICAL LSAME
+ EXTERNAL LSAME
+* ..
+* .. External Subroutines ..
+ EXTERNAL DLAMC2
+* ..
+* .. Save statement ..
+ SAVE FIRST, EPS, SFMIN, BASE, T, RND, EMIN, RMIN,
+ $ EMAX, RMAX, PREC
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ CALL DLAMC2( BETA, IT, LRND, EPS, IMIN, RMIN, IMAX, RMAX )
+ BASE = BETA
+ T = IT
+ IF( LRND ) THEN
+ RND = ONE
+ EPS = ( BASE**( 1-IT ) ) / 2
+ ELSE
+ RND = ZERO
+ EPS = BASE**( 1-IT )
+ END IF
+ PREC = EPS*BASE
+ EMIN = IMIN
+ EMAX = IMAX
+ SFMIN = RMIN
+ SMALL = ONE / RMAX
+ IF( SMALL.GE.SFMIN ) THEN
+*
+* Use SMALL plus a bit, to avoid the possibility of rounding
+* causing overflow when computing 1/sfmin.
+*
+ SFMIN = SMALL*( ONE+EPS )
+ END IF
+ END IF
+*
+ IF( LSAME( CMACH, 'E' ) ) THEN
+ RMACH = EPS
+ ELSE IF( LSAME( CMACH, 'S' ) ) THEN
+ RMACH = SFMIN
+ ELSE IF( LSAME( CMACH, 'B' ) ) THEN
+ RMACH = BASE
+ ELSE IF( LSAME( CMACH, 'P' ) ) THEN
+ RMACH = PREC
+ ELSE IF( LSAME( CMACH, 'N' ) ) THEN
+ RMACH = T
+ ELSE IF( LSAME( CMACH, 'R' ) ) THEN
+ RMACH = RND
+ ELSE IF( LSAME( CMACH, 'M' ) ) THEN
+ RMACH = EMIN
+ ELSE IF( LSAME( CMACH, 'U' ) ) THEN
+ RMACH = RMIN
+ ELSE IF( LSAME( CMACH, 'L' ) ) THEN
+ RMACH = EMAX
+ ELSE IF( LSAME( CMACH, 'O' ) ) THEN
+ RMACH = RMAX
+ END IF
+*
+ DLAMCH = RMACH
+ FIRST = .FALSE.
+ RETURN
+*
+* End of DLAMCH
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE DLAMC1( BETA, T, RND, IEEE1 )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ LOGICAL IEEE1, RND
+ INTEGER BETA, T
+* ..
+*
+* Purpose
+* =======
+*
+* DLAMC1 determines the machine parameters given by BETA, T, RND, and
+* IEEE1.
+*
+* Arguments
+* =========
+*
+* BETA (output) INTEGER
+* The base of the machine.
+*
+* T (output) INTEGER
+* The number of ( BETA ) digits in the mantissa.
+*
+* RND (output) LOGICAL
+* Specifies whether proper rounding ( RND = .TRUE. ) or
+* chopping ( RND = .FALSE. ) occurs in addition. This may not
+* be a reliable guide to the way in which the machine performs
+* its arithmetic.
+*
+* IEEE1 (output) LOGICAL
+* Specifies whether rounding appears to be done in the IEEE
+* 'round to nearest' style.
+*
+* Further Details
+* ===============
+*
+* The routine is based on the routine ENVRON by Malcolm and
+* incorporates suggestions by Gentleman and Marovich. See
+*
+* Malcolm M. A. (1972) Algorithms to reveal properties of
+* floating-point arithmetic. Comms. of the ACM, 15, 949-951.
+*
+* Gentleman W. M. and Marovich S. B. (1974) More on algorithms
+* that reveal properties of floating point arithmetic units.
+* Comms. of the ACM, 17, 276-277.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ LOGICAL FIRST, LIEEE1, LRND
+ INTEGER LBETA, LT
+ DOUBLE PRECISION A, B, C, F, ONE, QTR, SAVEC, T1, T2
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. Save statement ..
+ SAVE FIRST, LIEEE1, LBETA, LRND, LT
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ ONE = 1
+*
+* LBETA, LIEEE1, LT and LRND are the local values of BETA,
+* IEEE1, T and RND.
+*
+* Throughout this routine we use the function DLAMC3 to ensure
+* that relevant values are stored and not held in registers, or
+* are not affected by optimizers.
+*
+* Compute a = 2.0**m with the smallest positive integer m such
+* that
+*
+* fl( a + 1.0 ) = a.
+*
+ A = 1
+ C = 1
+*
+*+ WHILE( C.EQ.ONE )LOOP
+ 10 CONTINUE
+ IF( C.EQ.ONE ) THEN
+ A = 2*A
+ C = DLAMC3( A, ONE )
+ C = DLAMC3( C, -A )
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+* Now compute b = 2.0**m with the smallest positive integer m
+* such that
+*
+* fl( a + b ) .gt. a.
+*
+ B = 1
+ C = DLAMC3( A, B )
+*
+*+ WHILE( C.EQ.A )LOOP
+ 20 CONTINUE
+ IF( C.EQ.A ) THEN
+ B = 2*B
+ C = DLAMC3( A, B )
+ GO TO 20
+ END IF
+*+ END WHILE
+*
+* Now compute the base. a and c are neighbouring floating point
+* numbers in the interval ( beta**t, beta**( t + 1 ) ) and so
+* their difference is beta. Adding 0.25 to c is to ensure that it
+* is truncated to beta and not ( beta - 1 ).
+*
+ QTR = ONE / 4
+ SAVEC = C
+ C = DLAMC3( C, -A )
+ LBETA = C + QTR
+*
+* Now determine whether rounding or chopping occurs, by adding a
+* bit less than beta/2 and a bit more than beta/2 to a.
+*
+ B = LBETA
+ F = DLAMC3( B / 2, -B / 100 )
+ C = DLAMC3( F, A )
+ IF( C.EQ.A ) THEN
+ LRND = .TRUE.
+ ELSE
+ LRND = .FALSE.
+ END IF
+ F = DLAMC3( B / 2, B / 100 )
+ C = DLAMC3( F, A )
+ IF( ( LRND ) .AND. ( C.EQ.A ) )
+ $ LRND = .FALSE.
+*
+* Try and decide whether rounding is done in the IEEE 'round to
+* nearest' style. B/2 is half a unit in the last place of the two
+* numbers A and SAVEC. Furthermore, A is even, i.e. has last bit
+* zero, and SAVEC is odd. Thus adding B/2 to A should not change
+* A, but adding B/2 to SAVEC should change SAVEC.
+*
+ T1 = DLAMC3( B / 2, A )
+ T2 = DLAMC3( B / 2, SAVEC )
+ LIEEE1 = ( T1.EQ.A ) .AND. ( T2.GT.SAVEC ) .AND. LRND
+*
+* Now find the mantissa, t. It should be the integer part of
+* log to the base beta of a, however it is safer to determine t
+* by powering. So we find t as the smallest positive integer for
+* which
+*
+* fl( beta**t + 1.0 ) = 1.0.
+*
+ LT = 0
+ A = 1
+ C = 1
+*
+*+ WHILE( C.EQ.ONE )LOOP
+ 30 CONTINUE
+ IF( C.EQ.ONE ) THEN
+ LT = LT + 1
+ A = A*LBETA
+ C = DLAMC3( A, ONE )
+ C = DLAMC3( C, -A )
+ GO TO 30
+ END IF
+*+ END WHILE
+*
+ END IF
+*
+ BETA = LBETA
+ T = LT
+ RND = LRND
+ IEEE1 = LIEEE1
+ FIRST = .FALSE.
+ RETURN
+*
+* End of DLAMC1
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE DLAMC2( BETA, T, RND, EPS, EMIN, RMIN, EMAX, RMAX )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ LOGICAL RND
+ INTEGER BETA, EMAX, EMIN, T
+ DOUBLE PRECISION EPS, RMAX, RMIN
+* ..
+*
+* Purpose
+* =======
+*
+* DLAMC2 determines the machine parameters specified in its argument
+* list.
+*
+* Arguments
+* =========
+*
+* BETA (output) INTEGER
+* The base of the machine.
+*
+* T (output) INTEGER
+* The number of ( BETA ) digits in the mantissa.
+*
+* RND (output) LOGICAL
+* Specifies whether proper rounding ( RND = .TRUE. ) or
+* chopping ( RND = .FALSE. ) occurs in addition. This may not
+* be a reliable guide to the way in which the machine performs
+* its arithmetic.
+*
+* EPS (output) DOUBLE PRECISION
+* The smallest positive number such that
+*
+* fl( 1.0 - EPS ) .LT. 1.0,
+*
+* where fl denotes the computed value.
+*
+* EMIN (output) INTEGER
+* The minimum exponent before (gradual) underflow occurs.
+*
+* RMIN (output) DOUBLE PRECISION
+* The smallest normalized number for the machine, given by
+* BASE**( EMIN - 1 ), where BASE is the floating point value
+* of BETA.
+*
+* EMAX (output) INTEGER
+* The maximum exponent before overflow occurs.
+*
+* RMAX (output) DOUBLE PRECISION
+* The largest positive number for the machine, given by
+* BASE**EMAX * ( 1 - EPS ), where BASE is the floating point
+* value of BETA.
+*
+* Further Details
+* ===============
+*
+* The computation of EPS is based on a routine PARANOIA by
+* W. Kahan of the University of California at Berkeley.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ LOGICAL FIRST, IEEE, IWARN, LIEEE1, LRND
+ INTEGER GNMIN, GPMIN, I, LBETA, LEMAX, LEMIN, LT,
+ $ NGNMIN, NGPMIN
+ DOUBLE PRECISION A, B, C, HALF, LEPS, LRMAX, LRMIN, ONE, RBASE,
+ $ SIXTH, SMALL, THIRD, TWO, ZERO
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. External Subroutines ..
+ EXTERNAL DLAMC1, DLAMC4, DLAMC5
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC ABS, MAX, MIN
+* ..
+* .. Save statement ..
+ SAVE FIRST, IWARN, LBETA, LEMAX, LEMIN, LEPS, LRMAX,
+ $ LRMIN, LT
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. / , IWARN / .FALSE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ ZERO = 0
+ ONE = 1
+ TWO = 2
+*
+* LBETA, LT, LRND, LEPS, LEMIN and LRMIN are the local values of
+* BETA, T, RND, EPS, EMIN and RMIN.
+*
+* Throughout this routine we use the function DLAMC3 to ensure
+* that relevant values are stored and not held in registers, or
+* are not affected by optimizers.
+*
+* DLAMC1 returns the parameters LBETA, LT, LRND and LIEEE1.
+*
+ CALL DLAMC1( LBETA, LT, LRND, LIEEE1 )
+*
+* Start to find EPS.
+*
+ B = LBETA
+ A = B**( -LT )
+ LEPS = A
+*
+* Try some tricks to see whether or not this is the correct EPS.
+*
+ B = TWO / 3
+ HALF = ONE / 2
+ SIXTH = DLAMC3( B, -HALF )
+ THIRD = DLAMC3( SIXTH, SIXTH )
+ B = DLAMC3( THIRD, -HALF )
+ B = DLAMC3( B, SIXTH )
+ B = ABS( B )
+ IF( B.LT.LEPS )
+ $ B = LEPS
+*
+ LEPS = 1
+*
+*+ WHILE( ( LEPS.GT.B ).AND.( B.GT.ZERO ) )LOOP
+ 10 CONTINUE
+ IF( ( LEPS.GT.B ) .AND. ( B.GT.ZERO ) ) THEN
+ LEPS = B
+ C = DLAMC3( HALF*LEPS, ( TWO**5 )*( LEPS**2 ) )
+ C = DLAMC3( HALF, -C )
+ B = DLAMC3( HALF, C )
+ C = DLAMC3( HALF, -B )
+ B = DLAMC3( HALF, C )
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+ IF( A.LT.LEPS )
+ $ LEPS = A
+*
+* Computation of EPS complete.
+*
+* Now find EMIN. Let A = + or - 1, and + or - (1 + BASE**(-3)).
+* Keep dividing A by BETA until (gradual) underflow occurs. This
+* is detected when we cannot recover the previous A.
+*
+ RBASE = ONE / LBETA
+ SMALL = ONE
+ DO 20 I = 1, 3
+ SMALL = DLAMC3( SMALL*RBASE, ZERO )
+ 20 CONTINUE
+ A = DLAMC3( ONE, SMALL )
+ CALL DLAMC4( NGPMIN, ONE, LBETA )
+ CALL DLAMC4( NGNMIN, -ONE, LBETA )
+ CALL DLAMC4( GPMIN, A, LBETA )
+ CALL DLAMC4( GNMIN, -A, LBETA )
+ IEEE = .FALSE.
+*
+ IF( ( NGPMIN.EQ.NGNMIN ) .AND. ( GPMIN.EQ.GNMIN ) ) THEN
+ IF( NGPMIN.EQ.GPMIN ) THEN
+ LEMIN = NGPMIN
+* ( Non twos-complement machines, no gradual underflow;
+* e.g., VAX )
+ ELSE IF( ( GPMIN-NGPMIN ).EQ.3 ) THEN
+ LEMIN = NGPMIN - 1 + LT
+ IEEE = .TRUE.
+* ( Non twos-complement machines, with gradual underflow;
+* e.g., IEEE standard followers )
+ ELSE
+ LEMIN = MIN( NGPMIN, GPMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE IF( ( NGPMIN.EQ.GPMIN ) .AND. ( NGNMIN.EQ.GNMIN ) ) THEN
+ IF( ABS( NGPMIN-NGNMIN ).EQ.1 ) THEN
+ LEMIN = MAX( NGPMIN, NGNMIN )
+* ( Twos-complement machines, no gradual underflow;
+* e.g., CYBER 205 )
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE IF( ( ABS( NGPMIN-NGNMIN ).EQ.1 ) .AND.
+ $ ( GPMIN.EQ.GNMIN ) ) THEN
+ IF( ( GPMIN-MIN( NGPMIN, NGNMIN ) ).EQ.3 ) THEN
+ LEMIN = MAX( NGPMIN, NGNMIN ) - 1 + LT
+* ( Twos-complement machines with gradual underflow;
+* no known machine )
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN, GPMIN, GNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+ FIRST = .FALSE.
+***
+* Comment out this if block if EMIN is ok
+ IF( IWARN ) THEN
+ FIRST = .TRUE.
+ WRITE( 6, FMT = 9999 )LEMIN
+ END IF
+***
+*
+* Assume IEEE arithmetic if we found denormalised numbers above,
+* or if arithmetic seems to round in the IEEE style, determined
+* in routine DLAMC1. A true IEEE machine should have both things
+* true; however, faulty machines may have one or the other.
+*
+ IEEE = IEEE .OR. LIEEE1
+*
+* Compute RMIN by successive division by BETA. We could compute
+* RMIN as BASE**( EMIN - 1 ), but some machines underflow during
+* this computation.
+*
+ LRMIN = 1
+ DO 30 I = 1, 1 - LEMIN
+ LRMIN = DLAMC3( LRMIN*RBASE, ZERO )
+ 30 CONTINUE
+*
+* Finally, call DLAMC5 to compute EMAX and RMAX.
+*
+ CALL DLAMC5( LBETA, LT, LEMIN, IEEE, LEMAX, LRMAX )
+ END IF
+*
+ BETA = LBETA
+ T = LT
+ RND = LRND
+ EPS = LEPS
+ EMIN = LEMIN
+ RMIN = LRMIN
+ EMAX = LEMAX
+ RMAX = LRMAX
+*
+ RETURN
+*
+ 9999 FORMAT( / / ' WARNING. The value EMIN may be incorrect:-',
+ $ ' EMIN = ', I8, /
+ $ ' If, after inspection, the value EMIN looks',
+ $ ' acceptable please comment out ',
+ $ / ' the IF block as marked within the code of routine',
+ $ ' DLAMC2,', / ' otherwise supply EMIN explicitly.', / )
+*
+* End of DLAMC2
+*
+ END
+*
+************************************************************************
+*
+ DOUBLE PRECISION FUNCTION DLAMC3( A, B )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ DOUBLE PRECISION A, B
+* ..
+*
+* Purpose
+* =======
+*
+* DLAMC3 is intended to force A and B to be stored prior to doing
+* the addition of A and B , for use in situations where optimizers
+* might hold one of these in a register.
+*
+* Arguments
+* =========
+*
+* A (input) DOUBLE PRECISION
+* B (input) DOUBLE PRECISION
+* The values A and B.
+*
+* =====================================================================
+*
+* .. Executable Statements ..
+*
+ DLAMC3 = A + B
+*
+ RETURN
+*
+* End of DLAMC3
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE DLAMC4( EMIN, START, BASE )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ INTEGER BASE, EMIN
+ DOUBLE PRECISION START
+* ..
+*
+* Purpose
+* =======
+*
+* DLAMC4 is a service routine for DLAMC2.
+*
+* Arguments
+* =========
+*
+* EMIN (output) INTEGER
+* The minimum exponent before (gradual) underflow, computed by
+* setting A = START and dividing by BASE until the previous A
+* can not be recovered.
+*
+* START (input) DOUBLE PRECISION
+* The starting point for determining EMIN.
+*
+* BASE (input) INTEGER
+* The base of the machine.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ INTEGER I
+ DOUBLE PRECISION A, B1, B2, C1, C2, D1, D2, ONE, RBASE, ZERO
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. Executable Statements ..
+*
+ A = START
+ ONE = 1
+ RBASE = ONE / BASE
+ ZERO = 0
+ EMIN = 1
+ B1 = DLAMC3( A*RBASE, ZERO )
+ C1 = A
+ C2 = A
+ D1 = A
+ D2 = A
+*+ WHILE( ( C1.EQ.A ).AND.( C2.EQ.A ).AND.
+* $ ( D1.EQ.A ).AND.( D2.EQ.A ) )LOOP
+ 10 CONTINUE
+ IF( ( C1.EQ.A ) .AND. ( C2.EQ.A ) .AND. ( D1.EQ.A ) .AND.
+ $ ( D2.EQ.A ) ) THEN
+ EMIN = EMIN - 1
+ A = B1
+ B1 = DLAMC3( A / BASE, ZERO )
+ C1 = DLAMC3( B1*BASE, ZERO )
+ D1 = ZERO
+ DO 20 I = 1, BASE
+ D1 = D1 + B1
+ 20 CONTINUE
+ B2 = DLAMC3( A*RBASE, ZERO )
+ C2 = DLAMC3( B2 / RBASE, ZERO )
+ D2 = ZERO
+ DO 30 I = 1, BASE
+ D2 = D2 + B2
+ 30 CONTINUE
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+ RETURN
+*
+* End of DLAMC4
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE DLAMC5( BETA, P, EMIN, IEEE, EMAX, RMAX )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ LOGICAL IEEE
+ INTEGER BETA, EMAX, EMIN, P
+ DOUBLE PRECISION RMAX
+* ..
+*
+* Purpose
+* =======
+*
+* DLAMC5 attempts to compute RMAX, the largest machine floating-point
+* number, without overflow. It assumes that EMAX + abs(EMIN) sum
+* approximately to a power of 2. It will fail on machines where this
+* assumption does not hold, for example, the Cyber 205 (EMIN = -28625,
+* EMAX = 28718). It will also fail if the value supplied for EMIN is
+* too large (i.e. too close to zero), probably with overflow.
+*
+* Arguments
+* =========
+*
+* BETA (input) INTEGER
+* The base of floating-point arithmetic.
+*
+* P (input) INTEGER
+* The number of base BETA digits in the mantissa of a
+* floating-point value.
+*
+* EMIN (input) INTEGER
+* The minimum exponent before (gradual) underflow.
+*
+* IEEE (input) LOGICAL
+* A logical flag specifying whether or not the arithmetic
+* system is thought to comply with the IEEE standard.
+*
+* EMAX (output) INTEGER
+* The largest exponent before overflow
+*
+* RMAX (output) DOUBLE PRECISION
+* The largest machine floating-point number.
+*
+* =====================================================================
+*
+* .. Parameters ..
+ DOUBLE PRECISION ZERO, ONE
+ PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0 )
+* ..
+* .. Local Scalars ..
+ INTEGER EXBITS, EXPSUM, I, LEXP, NBITS, TRY, UEXP
+ DOUBLE PRECISION OLDY, RECBAS, Y, Z
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMC3
+ EXTERNAL DLAMC3
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MOD
+* ..
+* .. Executable Statements ..
+*
+* First compute LEXP and UEXP, two powers of 2 that bound
+* abs(EMIN). We then assume that EMAX + abs(EMIN) will sum
+* approximately to the bound that is closest to abs(EMIN).
+* (EMAX is the exponent of the required number RMAX).
+*
+ LEXP = 1
+ EXBITS = 1
+ 10 CONTINUE
+ TRY = LEXP*2
+ IF( TRY.LE.( -EMIN ) ) THEN
+ LEXP = TRY
+ EXBITS = EXBITS + 1
+ GO TO 10
+ END IF
+ IF( LEXP.EQ.-EMIN ) THEN
+ UEXP = LEXP
+ ELSE
+ UEXP = TRY
+ EXBITS = EXBITS + 1
+ END IF
+*
+* Now -LEXP is less than or equal to EMIN, and -UEXP is greater
+* than or equal to EMIN. EXBITS is the number of bits needed to
+* store the exponent.
+*
+ IF( ( UEXP+EMIN ).GT.( -LEXP-EMIN ) ) THEN
+ EXPSUM = 2*LEXP
+ ELSE
+ EXPSUM = 2*UEXP
+ END IF
+*
+* EXPSUM is the exponent range, approximately equal to
+* EMAX - EMIN + 1 .
+*
+ EMAX = EXPSUM + EMIN - 1
+ NBITS = 1 + EXBITS + P
+*
+* NBITS is the total number of bits needed to store a
+* floating-point number.
+*
+ IF( ( MOD( NBITS, 2 ).EQ.1 ) .AND. ( BETA.EQ.2 ) ) THEN
+*
+* Either there are an odd number of bits used to store a
+* floating-point number, which is unlikely, or some bits are
+* not used in the representation of numbers, which is possible,
+* (e.g. Cray machines) or the mantissa has an implicit bit,
+* (e.g. IEEE machines, Dec Vax machines), which is perhaps the
+* most likely. We have to assume the last alternative.
+* If this is true, then we need to reduce EMAX by one because
+* there must be some way of representing zero in an implicit-bit
+* system. On machines like Cray, we are reducing EMAX by one
+* unnecessarily.
+*
+ EMAX = EMAX - 1
+ END IF
+*
+ IF( IEEE ) THEN
+*
+* Assume we are on an IEEE machine which reserves one exponent
+* for infinity and NaN.
+*
+ EMAX = EMAX - 1
+ END IF
+*
+* Now create RMAX, the largest machine number, which should
+* be equal to (1.0 - BETA**(-P)) * BETA**EMAX .
+*
+* First compute 1.0 - BETA**(-P), being careful that the
+* result is less than 1.0 .
+*
+ RECBAS = ONE / BETA
+ Z = BETA - ONE
+ Y = ZERO
+ DO 20 I = 1, P
+ Z = Z*RECBAS
+ IF( Y.LT.ONE )
+ $ OLDY = Y
+ Y = DLAMC3( Y, Z )
+ 20 CONTINUE
+ IF( Y.GE.ONE )
+ $ Y = OLDY
+*
+* Now multiply by BETA**EMAX to get RMAX.
+*
+ DO 30 I = 1, EMAX
+ Y = DLAMC3( Y*BETA, ZERO )
+ 30 CONTINUE
+*
+ RMAX = Y
+ RETURN
+*
+* End of DLAMC5
+*
+ END
diff --git a/INSTALL/dlamchtst.f b/INSTALL/dlamchtst.f
new file mode 100644
index 00000000..fcdb0868
--- /dev/null
+++ b/INSTALL/dlamchtst.f
@@ -0,0 +1,40 @@
+ PROGRAM TEST3
+*
+* -- LAPACK test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Local Scalars ..
+ DOUBLE PRECISION BASE, EMAX, EMIN, EPS, PREC, RMAX, RMIN, RND,
+ $ SFMIN, T
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DLAMCH
+ EXTERNAL DLAMCH
+* ..
+* .. Executable Statements ..
+*
+ EPS = DLAMCH( 'Epsilon' )
+ SFMIN = DLAMCH( 'Safe minimum' )
+ BASE = DLAMCH( 'Base' )
+ PREC = DLAMCH( 'Precision' )
+ T = DLAMCH( 'Number of digits in mantissa' )
+ RND = DLAMCH( 'Rounding mode' )
+ EMIN = DLAMCH( 'Minimum exponent' )
+ RMIN = DLAMCH( 'Underflow threshold' )
+ EMAX = DLAMCH( 'Largest exponent' )
+ RMAX = DLAMCH( 'Overflow threshold' )
+*
+ WRITE( 6, * )' Epsilon = ', EPS
+ WRITE( 6, * )' Safe minimum = ', SFMIN
+ WRITE( 6, * )' Base = ', BASE
+ WRITE( 6, * )' Precision = ', PREC
+ WRITE( 6, * )' Number of digits in mantissa = ', T
+ WRITE( 6, * )' Rounding mode = ', RND
+ WRITE( 6, * )' Minimum exponent = ', EMIN
+ WRITE( 6, * )' Underflow threshold = ', RMIN
+ WRITE( 6, * )' Largest exponent = ', EMAX
+ WRITE( 6, * )' Overflow threshold = ', RMAX
+ WRITE( 6, * )' Reciprocal of safe minimum = ', 1 / SFMIN
+*
+ END
diff --git a/INSTALL/dsecnd_EXT_ETIME.f b/INSTALL/dsecnd_EXT_ETIME.f
new file mode 100644
index 00000000..16eec152
--- /dev/null
+++ b/INSTALL/dsecnd_EXT_ETIME.f
@@ -0,0 +1,33 @@
+ DOUBLE PRECISION FUNCTION DSECND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* DSECND returns the user time for a process in seconds.
+* This version gets the time from the EXTERNAL system function ETIME.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ REAL T1
+* ..
+* .. Local Arrays ..
+ REAL TARRAY( 2 )
+* ..
+* .. External Functions ..
+ REAL ETIME
+ EXTERNAL ETIME
+* ..
+* .. Executable Statements ..
+*
+ T1 = ETIME( TARRAY )
+ DSECND = TARRAY( 1 )
+ RETURN
+*
+* End of DSECND
+*
+ END
diff --git a/INSTALL/dsecnd_EXT_ETIME_.f b/INSTALL/dsecnd_EXT_ETIME_.f
new file mode 100644
index 00000000..b0690c45
--- /dev/null
+++ b/INSTALL/dsecnd_EXT_ETIME_.f
@@ -0,0 +1,33 @@
+ DOUBLE PRECISION FUNCTION DSECND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* DSECND returns the user time for a process in seconds.
+* This version gets the time from the system function ETIME_.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ REAL T1
+* ..
+* .. Local Arrays ..
+ REAL TARRAY( 2 )
+* ..
+* .. External Functions ..
+ REAL ETIME_
+ EXTERNAL ETIME_
+* ..
+* .. Executable Statements ..
+*
+ T1 = ETIME_( TARRAY )
+ DSECND = TARRAY( 1 )
+ RETURN
+*
+* End of DSECND
+*
+ END
diff --git a/INSTALL/dsecnd_INT_CPU_TIME.f b/INSTALL/dsecnd_INT_CPU_TIME.f
new file mode 100644
index 00000000..2b09012f
--- /dev/null
+++ b/INSTALL/dsecnd_INT_CPU_TIME.f
@@ -0,0 +1,31 @@
+ DOUBLE PRECISION FUNCTION DSECND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* DSECND returns the user time for a process in seconds.
+* This version gets the time from the INTERNAL function CPU_TIME.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+*
+ REAL T
+*
+* .. Intrinsic Functions ..
+*
+ INTRINSIC CPU_TIME
+*
+* .. Executable Statements .. *
+*
+ CALL CPU_TIME( T )
+ DSECND = T
+ RETURN
+*
+* End of DSECND
+*
+ END
diff --git a/INSTALL/dsecnd_INT_ETIME.f b/INSTALL/dsecnd_INT_ETIME.f
new file mode 100644
index 00000000..5f42421e
--- /dev/null
+++ b/INSTALL/dsecnd_INT_ETIME.f
@@ -0,0 +1,33 @@
+ DOUBLE PRECISION FUNCTION DSECND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* DSECND returns the user time for a process in seconds.
+* This version gets the time from the INTERNAL function ETIME.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ REAL T1
+* ..
+* .. Local Arrays ..
+ REAL TARRAY( 2 )
+* ..
+* .. Intrinsic Functions ..
+ REAL ETIME
+ INTRINSIC ETIME
+* ..
+* .. Executable Statements ..
+*
+ T1 = ETIME( TARRAY )
+ DSECND = TARRAY( 1 )
+ RETURN
+*
+* End of DSECND
+*
+ END
diff --git a/INSTALL/dsecnd_NONE.f b/INSTALL/dsecnd_NONE.f
new file mode 100644
index 00000000..c47aa40b
--- /dev/null
+++ b/INSTALL/dsecnd_NONE.f
@@ -0,0 +1,22 @@
+ DOUBLE PRECISION FUNCTION DSECND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* DSECND returns nothing instead of returning the user time for a process in seconds.
+* If you are using that routine, it means that neither EXTERNAL ETIME,
+* EXTERNAL ETIME_, INTERNAL ETIME, INTERNAL CPU_TIME is available on
+* your machine.
+*
+* =====================================================================
+*
+ DSECND = 0.0D+0
+ RETURN
+*
+* End of DSECND
+*
+ END
diff --git a/INSTALL/dsecndtst.f b/INSTALL/dsecndtst.f
new file mode 100644
index 00000000..45772068
--- /dev/null
+++ b/INSTALL/dsecndtst.f
@@ -0,0 +1,91 @@
+ PROGRAM TEST5
+*
+* -- LAPACK test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Parameters ..
+ INTEGER NMAX, ITS
+ PARAMETER ( NMAX = 100, ITS = 5000 )
+* ..
+* .. Local Scalars ..
+ INTEGER I, J
+ DOUBLE PRECISION ALPHA, AVG, T1, T2, TNOSEC
+* ..
+* .. Local Arrays ..
+ DOUBLE PRECISION X( NMAX ), Y( NMAX )
+* ..
+* .. External Functions ..
+ DOUBLE PRECISION DSECND
+ EXTERNAL DSECND
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC DBLE
+* ..
+* .. Executable Statements ..
+*
+*
+* Initialize X and Y
+*
+ DO 10 I = 1, NMAX
+ X( I ) = DBLE( 1 ) / DBLE( I )
+ Y( I ) = DBLE( NMAX-I ) / DBLE( NMAX )
+ 10 CONTINUE
+ ALPHA = 0.315D0
+*
+* Time 1,000,000 DAXPY operations
+*
+ T1 = DSECND( )
+ DO 30 J = 1, ITS
+ DO 20 I = 1, NMAX
+ Y( I ) = Y( I ) + ALPHA*X( I )
+ 20 CONTINUE
+ ALPHA = -ALPHA
+ 30 CONTINUE
+ T2 = DSECND( )
+ WRITE( 6, 9999 )T2 - T1
+ IF( T2-T1.GT.0.0D0 ) THEN
+ WRITE( 6, 9998 )1.0D0 / ( T2-T1 )
+ ELSE
+ WRITE( 6, 9994 )
+ END IF
+ TNOSEC = T2 - T1
+*
+* Time 1,000,000 DAXPY operations with DSECND in the outer loop
+*
+ T1 = DSECND( )
+ DO 50 J = 1, ITS
+ DO 40 I = 1, NMAX
+ Y( I ) = Y( I ) + ALPHA*X( I )
+ 40 CONTINUE
+ ALPHA = -ALPHA
+ T2 = DSECND( )
+ 50 CONTINUE
+*
+* Compute the time in milliseconds used by an average call
+* to DSECND.
+*
+ WRITE( 6, 9997 )T2 - T1
+ AVG = ( ( T2-T1 )-TNOSEC )*1000.D0 / DBLE( ITS )
+ WRITE( 6, 9996 )AVG
+*
+* Compute the equivalent number of floating point operations used
+* by an average call to DSECND.
+*
+ IF( TNOSEC.GT.0.0D0 )
+ $ WRITE( 6, 9995 )1000.D0*AVG / TNOSEC
+*
+ 9999 FORMAT( ' Time for 1,000,000 DAXPY ops = ', G10.3, ' seconds' )
+ 9998 FORMAT( ' DAXPY performance rate = ', G10.3, ' mflops ' )
+ 9997 FORMAT( ' Including DSECND, time = ', G10.3, ' seconds' )
+ 9996 FORMAT( ' Average time for DSECND = ', G10.3,
+ $ ' milliseconds' )
+ 9995 FORMAT( ' Equivalent floating point ops = ', G10.3, ' ops' )
+ 9994 FORMAT( ' *** Error: Time for operations was zero' )
+ CALL MYSUB(NMAX,X,Y)
+ END
+ SUBROUTINE MYSUB(N,X,Y)
+ INTEGER N
+ DOUBLE PRECISION X(N), Y(N)
+ RETURN
+ END
diff --git a/INSTALL/ilaver.f b/INSTALL/ilaver.f
new file mode 100644
index 00000000..57a455fa
--- /dev/null
+++ b/INSTALL/ilaver.f
@@ -0,0 +1,34 @@
+ SUBROUTINE ILAVER( VERS_MAJOR, VERS_MINOR, VERS_PATCH )
+*
+* -- LAPACK routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* January 2007
+*
+* .. Scalar Arguments ..
+ INTEGER VERS_MAJOR, VERS_MINOR, VERS_PATCH
+* ..
+*
+* Purpose
+* =======
+*
+* This subroutine return the Lapack version.
+*
+* Arguments
+* =========
+*
+* VERS_MAJOR (output) INTEGER
+* return the lapack major version
+* VERS_MINOR (output) INTEGER
+* return the lapack minor version from the major version
+* VERS_PATCH (output) INTEGER
+* return the lapack patch version from the minor version
+*
+* .. Executable Statements ..
+*
+ VERS_MAJOR = 3
+ VERS_MINOR = 1
+ VERS_PATCH = 1
+* =====================================================================
+*
+ RETURN
+ END
diff --git a/INSTALL/lawn81.tex b/INSTALL/lawn81.tex
new file mode 100644
index 00000000..c950b16b
--- /dev/null
+++ b/INSTALL/lawn81.tex
@@ -0,0 +1,1656 @@
+\documentclass[11pt]{report}
+
+\usepackage{indentfirst}
+\usepackage[body={6in,8.5in}]{geometry}
+\usepackage{hyperref}
+\usepackage{graphicx}
+\DeclareGraphicsRule{.ps}{eps}{}{}
+
+\renewcommand{\thesection}{\arabic{section}}
+\setcounter{tocdepth}{3}
+\setcounter{secnumdepth}{3}
+
+\begin{document}
+\begin{center}
+ {\Large LAPACK Working Note 81\\
+ Quick Installation Guide for LAPACK on Unix Systems\footnote{This work was
+ supported by NSF Grant No. ASC-8715728 and NSF Grant No. 0444486}}
+\end{center}
+\begin{center}
+% Edward Anderson\footnote{Current address: Cray Research Inc.,
+% 655F Lone Oak Drive, Eagan, MN 55121},
+ Authors and Jack Dongarra\\
+ Department of Computer Science \\
+ University of Tennessee \\
+ Knoxville, Tennessee 37996-1301 \\
+\end{center}
+\begin{center}
+ REVISED: VERSION 3.1.1, February 2007
+\end{center}
+
+\begin{center}
+Abstract
+\end{center}
+This working note describes how to install, and test version 3.1.1
+of LAPACK, a linear algebra package for high-performance
+computers, on a Unix System. The timing routines are not actually included in
+release 3.1.1, and that part of the LAWN refers to release 3.0.
+Non-Unix installation instructions and
+further details of the testing and timing suites are only contained in
+LAPACK Working Note 41, and not in this abbreviated version.
+%Separate instructions are provided for the Unix and non-Unix
+%versions of the test package.
+%Further details are also given on the design of the test and timing
+%programs.
+\newpage
+
+\tableofcontents
+
+\newpage
+% Introduction to Implementation Guide
+
+\section{Introduction}
+
+LAPACK is a linear algebra library for high-performance
+computers.
+The library includes Fortran 77 subroutines for
+the analysis and solution of systems of simultaneous linear algebraic
+equations, linear least-squares problems, and matrix eigenvalue
+problems.
+Our approach to achieving high efficiency is based on the use of
+a standard set of Basic Linear Algebra Subprograms (the BLAS),
+which can be optimized for each computing environment.
+By confining most of the computational work to the BLAS,
+the subroutines should be
+transportable and efficient across a wide range of computers.
+
+This working note describes how to install, test, and time this
+release of LAPACK on a Unix System.
+
+The instructions for installing, testing, and timing
+\footnote{timing are only provided in LAPACK 3.0 and before}
+are designed for a person whose
+responsibility is the maintenance of a mathematical software library.
+We assume the installer has experience in compiling and running
+Fortran programs and in creating object libraries.
+The installation process involves untarring the file, creating a set of
+libraries, and compiling and running the test and timing programs
+\footnotemark[\value{footnote}].
+
+%This guide combines the instructions for the Unix and non-Unix
+%versions of the LAPACK test package (the non-Unix version is in Appendix
+%~\ref{appendixe}).
+%At this time, the non-Unix version of LAPACK can only be obtained
+%after first untarring the Unix tar tape and then following the instructions in
+%Appendix ~\ref{appendixe}.
+
+Section~\ref{fileformat} describes how the files are organized in the
+file, and
+Section~\ref{overview} gives a general overview of the parts of the test package.
+Step-by-step instructions appear in Section~\ref{installation}.
+%for the Unix version and in the appendix for the non-Unix version.
+
+For users desiring additional information, please refer to LAPACK
+Working Note 41.
+% Sections~\ref{moretesting}
+%and ~\ref{moretiming} give
+%details of the test and timing programs and their input files.
+%Appendices ~\ref{appendixa} and ~\ref{appendixb} briefly describe
+%the LAPACK routines and auxiliary routines provided
+%in this release.
+%Appendix ~\ref{appendixc} lists the operation counts we have computed
+%for the BLAS and for some of the LAPACK routines.
+Appendix ~\ref{appendixd}, entitled ``Caveats'', is a compendium of the known
+problems from our own experiences, with suggestions on how to
+overcome them.
+
+\textbf{It is strongly advised that the user read Appendix
+A before proceeding with the installation process.}
+%Appendix E contains the execution times of the different test
+%and timing runs on two sample machines.
+%Appendix ~\ref{appendixe} contains the instructions to install LAPACK on a non-Unix
+%system.
+
+\section{Revisions Since the First Public Release}
+
+Since its first public release in February, 1992, LAPACK has had
+several updates, which have encompassed the introduction of new routines
+as well as extending the functionality of existing routines. The first
+update,
+June 30, 1992, was version 1.0a; the second update, October 31, 1992,
+was version 1.0b; the third update, March 31, 1993, was version 1.1;
+version 2.0 on September 30, 1994, coincided with the release of the
+Second Edition of the LAPACK Users' Guide;
+version 3.0 on June 30, 1999 coincided with the release of the Third Edition of
+the LAPACK Users' Guide;
+version 3.1 was released on November, 2006.
+and finally version 3.1.1 was released on November, 2007.
+
+All LAPACK routines reflect the current version number with the date
+on the routine indicating when it was last modified.
+For more information on revisions in the latest release, please refer
+to the \texttt{revisions.info} file in the lapack directory on netlib.
+\begin{quote}
+\url{http://www.netlib.org/lapack/revisions.info}
+\end{quote}
+
+%The distribution \texttt{tar} file \texttt{lapack.tar.z} that is
+%available on netlib is always the most up-to-date.
+%
+%On-line manpages (troff files) for LAPACK driver and computational
+%routines, as well as most of the BLAS routines, are available via
+%the \texttt{lapack} index on netlib.
+
+\section{File Format}\label{fileformat}
+
+The software for LAPACK is distributed in the form of a
+gzipped tar file (via anonymous ftp or the World Wide Web),
+which contains the Fortran source for LAPACK,
+the Basic Linear Algebra Subprograms
+(the Level 1, 2, and 3 BLAS) needed by LAPACK, the testing programs,
+and the timing programs\footnotemark[\value{footnote}].
+Users who wish to have a non-Unix installation should refer to LAPACK
+Working Note 41,
+although the overview in section~\ref{overview} applies to both the Unix and non-Unix
+versions.
+%Users who wish to have a non-Unix installation should go to Appendix ~\ref{appendixe},
+%although the overview in section ~\ref{overview} applies to both the Unix and non-Unix
+%versions.
+
+The package may be accessed via the World Wide Web through
+the URL address:
+\begin{quote}
+\url{http://www.netlib.org/lapack/lapack.tgz}
+\end{quote}
+
+Or, you can retrieve the file via anonymous ftp at netlib:
+
+\begin{verbatim}
+ ftp ftp.netlib.org
+ login: anonymous
+ password: <your email address>
+ cd lapack
+ binary
+ get lapack.tgz
+ quit
+\end{verbatim}
+
+The software in the \texttt{tar} file
+is organized in a number of essential directories as shown
+in Figure 1. Please note that this figure does not reflect everything
+that is contained in the \texttt{LAPACK} directory. Input and instructional
+files are also located at various levels.
+\begin{figure}
+\vspace{11pt}
+\centerline{\includegraphics[width=6.5in,height=3in]{org2.ps}}
+\caption{Unix organization of LAPACK 3.0}
+\vspace{11pt}
+\end{figure}
+Libraries are created in the LAPACK directory and
+executable files are created in one of the directories BLAS, TESTING,
+or TIMING\footnotemark[\value{footnote}]. Input files for the test and
+timing\footnotemark[\value{footnote}] programs are also
+found in these three directories so that testing may be carried out
+in the directories LAPACK/BLAS, LAPACK/TESTING, and LAPACK/TIMING \footnotemark[\value{footnote}].
+A top-level makefile in the LAPACK directory is provided to perform the
+entire installation procedure.
+
+\section{Overview of Tape Contents}\label{overview}
+
+Most routines in LAPACK occur in four versions: REAL,
+DOUBLE PRECISION, COMPLEX, and COMPLEX*16.
+The first three versions (REAL, DOUBLE PRECISION, and COMPLEX)
+are written in standard Fortran 77 and are completely portable;
+the COMPLEX*16 version is provided for
+those compilers which allow this data type.
+For convenience, we often refer to routines by their single precision
+names; the leading `S' can be replaced by a `D' for double precision,
+a `C' for complex, or a `Z' for complex*16.
+For LAPACK use and testing you must decide which version(s)
+of the package you intend to install at your site (for example,
+REAL and COMPLEX on a Cray computer or DOUBLE PRECISION and
+COMPLEX*16 on an IBM computer).
+
+\subsection{LAPACK Routines}
+
+There are three classes of LAPACK routines:
+\begin{itemize}
+
+\item \textbf{driver} routines solve a complete problem, such as solving
+a system of linear equations or computing the eigenvalues of a real
+symmetric matrix. Users are encouraged to use a driver routine if there
+is one that meets their requirements. The driver routines are listed
+in LAPACK Working Note 41~\cite{WN41} and the LAPACK Users' Guide~\cite{LUG}.
+%in Appendix ~\ref{appendixa}.
+
+\item \textbf{computational} routines, also called simply LAPACK routines,
+perform a distinct computational task, such as computing
+the $LU$ decomposition of an $m$-by-$n$ matrix or finding the
+eigenvalues and eigenvectors of a symmetric tridiagonal matrix using
+the $QR$ algorithm.
+The LAPACK routines are listed in LAPACK Working Note 41~\cite{WN41}
+and the LAPACK Users' Guide~\cite{LUG}.
+%The LAPACK routines are listed in Appendix ~\ref{appendixa}; see also LAPACK
+%Working Note \#5 \cite{WN5}.
+
+\item \textbf{auxiliary} routines are all the other subroutines called
+by the driver routines and computational routines.
+%Among them are subroutines to perform subtasks of block algorithms,
+%in particular, the unblocked versions of the block algorithms;
+%extensions to the BLAS, such as matrix-vector operations involving
+%complex symmetric matrices;
+%the special routines LSAME and XERBLA which first appeared with the
+%BLAS;
+%and a number of routines to perform common low-level computations,
+%such as computing a matrix norm, generating an elementary Householder
+%transformation, and applying a sequence of plane rotations.
+%Many of the auxiliary routines may be of use to numerical analysts
+%or software developers, so we have documented the Fortran source for
+%these routines with the same level of detail used for the LAPACK
+%routines and driver routines.
+The auxiliary routines are listed in LAPACK Working Note 41~\cite{WN41}
+and the LAPACK Users' Guide~\cite{LUG}.
+%The auxiliary routines are listed in Appendix ~\ref{appendixb}.
+\end{itemize}
+
+\subsection{Level 1, 2, and 3 BLAS}
+
+The BLAS are a set of Basic Linear Algebra Subprograms that perform
+vector-vector, matrix-vector, and matrix-matrix operations.
+LAPACK is designed around the Level 1, 2, and 3 BLAS, and nearly all
+of the parallelism in the LAPACK routines is contained in the BLAS.
+Therefore,
+the key to getting good performance from LAPACK lies in having an
+efficient version of the BLAS optimized for your particular machine.
+Optimized BLAS libraries are available on a variety of architectures,
+refer to the BLAS FAQ on netlib for further information.
+\begin{quote}
+\url{http://www.netlib.org/blas/faq.html}
+\end{quote}
+There are also freely available BLAS generators that automatically
+tune a subset of the BLAS for a given architecture. E.g.,
+\begin{quote}
+\url{http://www.netlib.org/atlas/}
+\end{quote}
+And, if all else fails, there is the Fortran~77 reference implementation
+of the Level 1, 2, and 3 BLAS available on netlib (also included in
+the LAPACK distribution tar file).
+\begin{quote}
+\url{http://www.netlib.org/blas/blas.tgz}
+\end{quote}
+No matter which BLAS library is used, the BLAS test programs should
+always be run.
+
+Users should not expect too much from the Fortran~77 reference implementation
+BLAS; these versions were written to define the basic operations and do not
+employ the standard tricks for optimizing Fortran code.
+
+The formal definitions of the Level 1, 2, and 3 BLAS
+are in \cite{BLAS1}, \cite{BLAS2}, and \cite{BLAS3}.
+The BLAS Quick Reference card is available on netlib.
+
+\subsection{LAPACK Test Routines}
+
+This release contains two distinct test programs for LAPACK routines
+in each data type. One test program tests the routines for solving
+linear equations and linear least squares problems,
+and the other tests routines for the matrix eigenvalue problem.
+The routines for generating test matrices are used by both test
+programs and are compiled into a library for use by both test programs.
+
+\subsection{LAPACK Timing Routines (for LAPACK 3.0 and before) }
+
+This release also contains two distinct timing programs for the
+LAPACK routines in each data type.
+The linear equation timing program gathers performance data in
+megaflops on the factor, solve, and inverse routines for solving
+linear systems, the routines to generate or apply an orthogonal matrix
+given as a sequence of elementary transformations, and the reductions
+to bidiagonal, tridiagonal, or Hessenberg form for eigenvalue
+computations.
+The operation counts used in computing the megaflop rates are computed
+from a formula;
+see LAPACK Working Note 41~\cite{WN41}.
+% see Appendix ~\ref{appendixc}.
+The eigenvalue timing program is used with the eigensystem routines
+and returns the execution time, number of floating point operations, and
+megaflop rate for each of the requested subroutines.
+In this program, the number of operations is computed while the
+code is executing using special instrumented versions of the LAPACK
+subroutines.
+
+\section{Installing LAPACK on a Unix System}\label{installation}
+
+Installing, testing, and timing\footnotemark[\value{footnote}] the Unix version of LAPACK
+involves the following steps:
+\begin{enumerate}
+\item Gunzip and tar the file.
+
+\item Copy and edit the file \texttt{LAPACK/make.inc.example to LAPACK/make.inc}.
+
+\item Edit the file \texttt{LAPACK/Makefile} and type \texttt{make}.
+
+%\item Test and Install the Machine-Dependent Routines \\
+%\emph{(WARNING: You may need to supply a correct version of second.f and
+%dsecnd.f for your machine)}
+%{\tt
+%\begin{list}{}{}
+%\item cd LAPACK
+%\item make install
+%\end{list} }
+%
+%\item Create the BLAS Library, \emph{if necessary} \\
+%\emph{(NOTE: For best performance, it is recommended you use the manufacturers' BLAS)}
+%{\tt
+%\begin{list}{}{}
+%\item \texttt{cd LAPACK}
+%\item \texttt{make blaslib}
+%\end{list} }
+%
+%\item Run the Level 1, 2, and 3 BLAS Test Programs
+%\begin{list}{}{}
+%\item \texttt{cd LAPACK}
+%\item \texttt{make blas\_testing}
+%\end{list}
+%
+%\item Create the LAPACK Library
+%\begin{list}{}{}
+%\item \texttt{cd LAPACK}
+%\item \texttt{make lapacklib}
+%\end{list}
+%
+%\item Create the Library of Test Matrix Generators
+%\begin{list}{}{}
+%\item \texttt{cd LAPACK}
+%\item \texttt{make tmglib}
+%\end{list}
+%
+%\item Run the LAPACK Test Programs
+%\begin{list}{}{}
+%\item \texttt{cd LAPACK}
+%\item \texttt{make testing}
+%\end{list}
+%
+%\item Run the LAPACK Timing Programs
+%\begin{list}{}{}
+%\item \texttt{cd LAPACK}
+%\item \texttt{make timing}
+%\end{list}
+%
+%\item Run the BLAS Timing Programs
+%\begin{list}{}{}
+%\item \texttt{cd LAPACK}
+%\item \texttt{make blas\_timing}
+%\end{list}
+\end{enumerate}
+
+\subsection{Untar the File}
+
+If you received a tar file of LAPACK via the World Wide
+Web or anonymous ftp, enter the following command:
+
+\begin{list}{}
+\item{\texttt{gunzip -c lapack.tgz | tar xvf -}}
+\end{list}
+
+\noindent
+This will create a top-level directory called \texttt{LAPACK}, which
+requires approximately 34 Mbytes of disk space.
+The total space requirements including the object files and executables
+is approximately 100 Mbytes for all four data types.
+
+\subsection{Copy and edit the file \texttt{LAPACK/make.inc.example to LAPACK/make.inc}}
+
+Before the libraries can be built, or the testing and timing\footnotemark[\value{footnote}] programs
+run, you must define all machine-specific parameters for the
+architecture to which you are installing LAPACK. All machine-specific
+parameters are contained in the file \texttt{LAPACK/make.inc}.
+An example of \texttt{LAPACK/make.inc} for a LINUX machine with GNU compilers is given
+in \texttt{LAPACK/make.inc.example}, copy that file to LAPACK/make.inc by entering the following command:
+
+\begin{list}{}
+\item{\texttt{cp LAPACK/make.inc.example LAPACK/make.inc}}
+\end{list}
+
+\noindent
+Now modify your \texttt{LAPACK/make.inc} by applying the following recommendations.
+The first line of this \texttt{make.inc} file is:
+\begin{quote}
+SHELL = /bin/sh
+\end{quote}
+and it will need to be modified to \texttt{SHELL = /sbin/sh} if you are
+installing LAPACK on an SGI architecture.
+Second, you will
+need to modify the \texttt{PLAT} definition, which is appended to all
+library names, to specify the architecture to which you are installing
+LAPACK. This features avoids confusion in library names when you are
+installing LAPACK on more than one architecture. Next, you will need
+to modify \texttt{FORTRAN}, \texttt{OPTS}, \texttt{DRVOPTS}, \texttt{NOOPT}, \texttt{LOADER},
+and \texttt{LOADOPTS} to specify
+the compiler, compiler options, compiler options for the testing and
+timing\footnotemark[\value{footnote}] main programs, loader, loader options.
+Next you will have to choose which function you will use to time in the \texttt{SECOND} and \texttt{DSECND} routines.
+\begin{verbatim}
+#The Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value...
+# In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+\end{verbatim}
+Refer to the section~\ref{second} to get more information.
+
+
+Next, you will need to modify \texttt{ARCH}, \texttt{ARCHFLAGS}, and \texttt{RANLIB} to specify archiver,
+archiver options, and ranlib for your machine. If your architecture
+does not require \texttt{ranlib} to be run after each archive command (as
+is the case with CRAY computers running UNICOS, Hewlett Packard
+computers running HP-UX, or SUN SPARCstations running Solaris), set
+\texttt{ranlib=echo}. And finally, you must
+modify the \texttt{BLASLIB} definition to specify the BLAS library to which
+you will be linking. If an optimized version of the BLAS is available
+on your machine, you are highly recommended to link to that library.
+Otherwise, by default, \texttt{BLASLIB} is set to the Fortran 77 version. \\
+
+\textbf{NOTE:} Example \texttt{make.inc} include files are contained in the
+\texttt{LAPACK/INSTALL} directory. Please refer to
+Appendix~\ref{appendixd} for machine-specific installation hints, and/or
+the \texttt{release\_notes} file on \texttt{netlib}.
+\begin{quote}
+\url{http://www.netlib.org/lapack/release\_notes}
+\end{quote}
+
+\subsection{Edit the file \texttt{LAPACK/Makefile}}\label{toplevelmakefile}
+
+This \texttt{Makefile} can be modified to perform as much of the
+installation process as the user desires. Ideally, this is the ONLY
+makefile the user must modify. However, modification of lower-level
+makefiles may be necessary if a specific routine needs to be compiled
+with a different level of optimization.
+
+First, edit the definitions of \texttt{blaslib}, \texttt{lapacklib},
+\texttt{tmglib}, \texttt{lapack\_testing}, and \texttt{timing}\footnotemark[\value{footnote}] in the file \texttt{LAPACK/Makefile}
+to specify the data types desired. For example,
+if you only wish to compile the single precision real version of the
+LAPACK library, you would modify the \texttt{lapacklib} definition to be:
+
+\begin{verbatim}
+lapacklib:
+ ( cd SRC; $(MAKE) single )
+\end{verbatim}
+
+Likewise, you could specify \texttt{double, complex, or complex16} to
+build the double precision real, single precision complex, or double
+precision complex libraries, respectively. By default, the presence of
+no arguments following the \texttt{make} command will result in the
+building of all four data types.
+The make command can be run more than once to add another
+data type to the library if necessary.
+
+%If you are installing LAPACK on a Silicon Graphics machine, you must
+%modify the respective definitions of \texttt{testing} and \texttt{timing} to be
+%\begin{verbatim}
+%testing:
+% ( cd TESTING; $(MAKE) -f Makefile.sgi )
+%\end{verbatim}
+%and
+%\begin{verbatim}
+%timing:
+% ( cd TIMING; $(MAKE) -f Makefile.sgi )
+%\end{verbatim}
+
+Next, if you will be using a locally available BLAS library, you will need
+to remove \texttt{blaslib} from the \texttt{lib} definition. And finally,
+if you do not wish to build all of the libraries individually and
+likewise run all of the testing and timing separately, you can
+modify the \texttt{all} definition to specify the amount of the
+installation process that you want performed. By default,
+the \texttt{all} definition is set to
+\begin{verbatim}
+all: lapack_install lib lapack_testing blas_testing
+\end{verbatim}
+which will perform all phases of the installation
+process -- testing of machine-dependent routines, building the libraries,
+BLAS testing and LAPACK testing.
+
+The entire installation process will then be performed by typing
+\texttt{make}.
+
+Questions and/or comments can be directed to the
+authors as described in Section~\ref{sendresults}. If test failures
+occur, please refer to the appropriate subsection in
+Section~\ref{furtherdetails}.
+
+If disk space is limited, we suggest building each data type separately
+and/or deleting all object files after building the libraries. Likewise, all
+testing and timing executables can be deleted after the testing and timing
+process is completed. The removal of all object files and executables
+can be accomplished by the following:
+
+\begin{list}{}{}
+\item \texttt{cd LAPACK}
+\item \texttt{make clean}
+\end{list}
+
+\section{Further Details of the Installation Process}\label{furtherdetails}
+
+Alternatively, you can choose to run each of the phases of the
+installation process separately. The following sections give details
+on how this may be achieved.
+
+\subsection{Test and Install the Machine-Dependent Routines.}
+
+There are six machine-dependent functions in the test and timing
+package, at least three of which must be installed. They are
+
+\begin{tabbing}
+MONOMO \= DOUBLE PRECYSION \= \kill
+LSAME \> LOGICAL \> Test if two characters are the same regardless of case \\
+SLAMCH \> REAL \> Determine machine-dependent parameters \\
+DLAMCH \> DOUBLE PRECISION \> Determine machine-dependent parameters \\
+SECOND \> REAL \> Return time in seconds from a fixed starting time \\
+DSECND \> DOUBLE PRECISION \> Return time in seconds from a fixed starting time\\
+ILAENV \> INTEGER \> Checks that NaN and infinity arithmetic are IEEE-754 compliant
+\end{tabbing}
+
+\noindent
+If you are working only in single precision, you do not need to install
+DLAMCH and DSECND, and if you are working only in double precision,
+you do not need to install SLAMCH and SECOND.
+
+These six subroutines are provided in \texttt{LAPACK/INSTALL},
+along with six test programs.
+To compile the six test programs and run the tests, go to \texttt{LAPACK} and
+type \texttt{make lapack\_install}. The test programs are called
+\texttt{testlsame, testslamch, testdlamch, testsecond, testdsecnd} and
+\texttt{testieee}.
+If you do not wish to run all tests, you will need to modify the
+\texttt{lapack\_install} definition in the \texttt{LAPACK/Makefile} to only include the
+tests you wish to run. Otherwise, all tests will be performed.
+The expected results of each test program are described below.
+
+\subsubsection{Installing LSAME}
+
+LSAME is a logical function with two character parameters, A and B.
+It returns .TRUE. if A and B are the same regardless of case, or .FALSE.
+if they are different.
+For example, the expression
+
+\begin{list}{}{}
+\item \texttt{LSAME( UPLO, 'U' )}
+\end{list}
+\noindent
+is equivalent to
+\begin{list}{}{}
+\item \texttt{( UPLO.EQ.'U' ).OR.( UPLO.EQ.'u' )}
+\end{list}
+
+The test program in \texttt{lsametst.f} tests all combinations of
+the same character in upper and lower case for A and B, and two
+cases where A and B are different characters.
+
+Run the test program by typing \texttt{testlsame}.
+If LSAME works correctly, the only message you should see after the
+execution of \texttt{testlsame} is
+\begin{verbatim}
+ ASCII character set
+ Tests completed
+\end{verbatim}
+The file \texttt{lsame.f} is automatically copied to
+\texttt{LAPACK/BLAS/SRC/} and \texttt{LAPACK/SRC/}.
+The function LSAME is needed by both the BLAS and LAPACK, so it is safer
+to have it in both libraries as long as this does not cause trouble
+in the link phase when both libraries are used.
+
+\subsubsection{Installing SLAMCH and DLAMCH}
+
+SLAMCH and DLAMCH are real functions with a single character parameter
+that indicates the machine parameter to be returned. The test
+program in \texttt{slamchtst.f}
+simply prints out the different values computed by SLAMCH,
+so you need to know something about what the values should be.
+For example, the output of the test program executable \texttt{testslamch}
+for SLAMCH on a Sun SPARCstation is
+\begin{verbatim}
+ Epsilon = 5.96046E-08
+ Safe minimum = 1.17549E-38
+ Base = 2.00000
+ Precision = 1.19209E-07
+ Number of digits in mantissa = 24.0000
+ Rounding mode = 1.00000
+ Minimum exponent = -125.000
+ Underflow threshold = 1.17549E-38
+ Largest exponent = 128.000
+ Overflow threshold = 3.40282E+38
+ Reciprocal of safe minimum = 8.50706E+37
+\end{verbatim}
+On a Cray machine, the safe minimum underflows its output
+representation and the overflow threshold overflows its output
+representation, so the safe minimum is printed as 0.00000 and overflow
+is printed as R. This is normal.
+If you would prefer to print a representable number, you can modify
+the test program to print SFMIN*100. and RMAX/100. for the safe
+minimum and overflow thresholds.
+
+Likewise, the test executable \texttt{testdlamch} is run for DLAMCH.
+
+If both tests were successful, go to Section~\ref{second}.
+
+If SLAMCH (or DLAMCH) returns an invalid value, you will have to create
+your own version of this function. The following options are used in
+LAPACK and must be set:
+
+\begin{list}{}{}
+\item {`B': } Base of the machine
+\item {`E': } Epsilon (relative machine precision)
+\item {`O': } Overflow threshold
+\item {`P': } Precision = Epsilon*Base
+\item {`S': } Safe minimum (often same as underflow threshold)
+\item {`U': } Underflow threshold
+\end{list}
+
+Some people may be familiar with R1MACH (D1MACH), a primitive
+routine for setting machine parameters in which the user must
+comment out the appropriate assignment statements for the target
+machine. If a version of R1MACH is on hand, the assignments in
+SLAMCH can be made to refer to R1MACH using the correspondence
+
+\begin{list}{}{}
+\item {SLAMCH( `U' )} $=$ R1MACH( 1 )
+\item {SLAMCH( `O' )} $=$ R1MACH( 2 )
+\item {SLAMCH( `E' )} $=$ R1MACH( 3 )
+\item {SLAMCH( `B' )} $=$ R1MACH( 5 )
+\end{list}
+
+\noindent
+The safe minimum returned by SLAMCH( 'S' ) is initially set to the
+underflow value, but if $1/(\mathrm{overflow}) \geq (\mathrm{underflow})$
+it is recomputed as $(1/(\mathrm{overflow})) * ( 1 + \varepsilon )$,
+where $\varepsilon$ is the machine precision.
+
+BE AWARE that the initial call to SLAMCH or DLAMCH is expensive.
+We suggest that installers run it once, save the results, and hard-code
+the constants in the version they put in their library.
+
+\subsubsection{Installing SECOND and DSECND}\label{second}
+
+Both the timing routines\footnotemark[\value{footnote}] and the test routines call SECOND
+(DSECND), a real function with no arguments that returns the time
+in seconds from some fixed starting time.
+Our version of this routine
+returns only ``user time'', and not ``user time $+$ system time''.
+The following version of SECOND in \texttt{second\_EXT\_ETIME.f, second\_INT\_ETIME.f} calls
+ETIME, a Fortran library routine available on some computer systems.
+If ETIME is not available or a better local timing function exists,
+you will have to provide the correct interface to SECOND and DSECND
+on your machine.
+
+Since LAPACK 3.1.1 we provide 5 different flavours of the SECOND and DSECND routines.
+The version that will be used depends on the value of the TIMER variable in the make.inc
+
+\begin{itemize}
+\item If ETIME is available as an external function, set the value of the TIMER variable in your
+make.inc to \texttt{EXT\_ETIME}:\texttt{second\_EXT\_ETIME.f} and \texttt{dsecnd\_EXT\_ETIME.f} will be used.
+Usually on HPPA architectures,
+the compiler and loader flag \texttt{+U77} should be included to access
+the function \texttt{ETIME}.
+
+\item If ETIME\_ is available as an external function, set the value of the TIMER variable in your make.inc
+to \texttt{EXT\_ETIME\_}:\texttt{second\_EXT\_ETIME\_.f} and \texttt{dsecnd\_EXT\_ETIME\_.f} will be used.
+It is the case on some IBM architectures such as IBM RS/6000s.
+
+\item If ETIME is available as an internal function, set the value of the TIMER variable in your make.inc
+to \texttt{INT\_ETIME}:\texttt{second\_INT\_ETIME.f} and \texttt{dsecnd\_INT\_ETIME.f} will be used.
+This is the case with gfortan.
+
+\item If CPU\_TIME is available as an internal function, set the value of the TIMER variable in your make.inc
+to \texttt{INT\_CPU\_TIME}:\texttt{second\_INT\_CPU\_TIME.f} and \texttt{dsecnd\_INT\_CPU\_TIME.f} will be used.
+
+\item If none of these function is available, set the value of the TIMER variable in your make.inc
+to \texttt{NONE:}\texttt{second\_NONE.f} and \texttt{dsecnd\_NONE.f} will be used.
+These routines will always return zero.
+\end{itemize}
+
+The test program in \texttt{secondtst.f}
+performs a million operations using 5000 iterations of
+the SAXPY operation $y := y + \alpha x$ on a vector of length 100.
+The total time and megaflops for this test is reported, then
+the operation is repeated including a call to SECOND on each of
+the 5000 iterations to determine the overhead due to calling SECOND.
+The test program executable is called \texttt{testsecond} (or \texttt{testdsecnd}).
+There is no single right answer, but the times
+in seconds should be positive and the megaflop ratios should be
+appropriate for your machine.
+
+\subsubsection{Testing IEEE arithmetic and ILAENV}\label{testieee}
+
+%\textbf{If you are installing LAPACK on a non-IEEE machine, you MUST
+%modify ILAENV! Otherwise, ILAENV will crash . By default, ILAENV
+%assumes an IEEE machine, and does a test for IEEE-754 compliance.}
+
+As some new routines in LAPACK rely on IEEE-754 compliance,
+two settings (\texttt{ISPEC=10} and \texttt{ISPEC=11}) have been added to ILAENV
+(\texttt{LAPACK/SRC/ilaenv.f}) to denote IEEE-754 compliance for NaN and
+infinity arithmetic, respectively. By default, ILAENV assumes an IEEE
+machine, and does a test for IEEE-754 compliance. \textbf{NOTE: If you
+are installing LAPACK on a non-IEEE machine, you MUST modify ILAENV,
+as this test inside ILAENV will crash!}
+
+If \texttt{ILAENV( 10, $\ldots$ )} or \texttt{ILAENV( 11, $\ldots$ )} is
+issued, then \texttt{ILAENV=1} is returned to signal IEEE-754 compliance,
+and \texttt{ILAENV=0} if the architecture is non-IEEE-754 compliant.
+
+Thus, for non-IEEE machines, the user must hard-code the setting of
+(\texttt{ILAENV=0}) for (\texttt{ISPEC=10} and \texttt{ISPEC=11}) in the version
+of \texttt{LAPACK/SRC/ilaenv.f} to be put in
+his library. There are also specialized testing and timing\footnotemark[\value{footnote}] versions of
+ILAENV that will also need to be modified.
+\begin{itemize}
+\item Testing/timing version of \texttt{LAPACK/TESTING/LIN/ilaenv.f}
+\item Testing/timing version of \texttt{LAPACK/TESTING/EIG/ilaenv.f}
+\item Testing/timing version of \texttt{LAPACK/TIMING/LIN/ilaenv.f}
+\item Testing/timing version of \texttt{LAPACK/TIMING/EIG/ilaenv.f}
+\end{itemize}
+
+%Some new routines in LAPACK rely on IEEE-754 compliance, and if non-compliance
+%is detected (via a call to the function ILAENV), alternative (slower)
+%algorithms will be chosen.
+%For further details, refer to the leading comments of routines such
+%as \texttt{LAPACK/SRC/sstevr.f}.
+
+The test program in \texttt{LAPACK/INSTALL/tstiee.f} checks an installation
+architecture
+to see if infinity arithmetic and NaN arithmetic are IEEE-754 compliant.
+A warning message to the user is printed if non-compliance is detected.
+This same test is performed inside the function ILAENV. If
+\texttt{ILAENV( 10, $\ldots$ )} or \texttt{ILAENV( 11, $\ldots$ )} is
+issued, then \texttt{ILAENV=1} is returned to signal IEEE-754 compliance,
+and \texttt{ILAENV=0} if the architecture is non-IEEE-754 compliant.
+
+To avoid this IEEE test being run every time you call
+\texttt{ILAENV( 10, $\ldots$)} or \texttt{ILAENV( 11, $\ldots$ )}, we suggest
+that the user hard-code the setting of
+\texttt{ILAENV=1} or \texttt{ILAENV=0} in the version of \texttt{LAPACK/SRC/ilaenv.f} to be put in
+his library. As aforementioned, there are also specialized testing and
+timing\footnotemark[\value{footnote}] versions of ILAENV that will also need to be modified.
+
+\subsection{Create the BLAS Library}
+
+Ideally, a highly optimized version of the BLAS library already
+exists on your machine.
+In this case you can go directly to Section~\ref{testblas} to
+make the BLAS test programs.
+
+\begin{itemize}
+\item[a)]
+Go to \texttt{LAPACK} and edit the definition of \texttt{blaslib} in the
+file \texttt{Makefile} to specify the data types desired, as in the example
+in Section~\ref{toplevelmakefile}.
+
+If you already have some of the BLAS, you will need to edit the file
+\texttt{LAPACK/BLAS/SRC/Makefile} to comment out the lines
+defining the BLAS you have.
+
+\item[b)]
+Type \texttt{make blaslib}.
+The make command can be run more than once to add another
+data type to the library if necessary.
+\end{itemize}
+
+\noindent
+The BLAS library is created in \texttt{LAPACK/blas\_PLAT.a}, where
+\texttt{PLAT} is the user-defined architecture suffix specified in the file
+\texttt{LAPACK/make.inc}.
+
+\subsection{Run the BLAS Test Programs}\label{testblas}
+
+Test programs for the Level 1, 2, and 3 BLAS are in the directory
+\texttt{LAPACK/BLAS/TESTING}.
+
+To compile and run the Level 1, 2, and 3 BLAS test programs,
+go to \texttt{LAPACK} and type \texttt{make blas\_testing}. The executable
+files are called \texttt{xblat\_s}, \texttt{xblat\_d}, \texttt{xblat\_c}, and
+\texttt{xblat\_z}, where the \_ (underscore) is replaced by 1, 2, or 3,
+depending upon the level of BLAS that it is testing. All executable and
+output files are created in \texttt{LAPACK/BLAS/}.
+For the Level 1 BLAS tests, the output file names are \texttt{sblat1.out},
+\texttt{dblat1.out}, \texttt{cblat1.out}, and \texttt{zblat1.out}. For the Level
+2 and 3 BLAS, the name of the output file is indicated on the first line of the
+input file and is currently defined to be \texttt{sblat2.out} for
+the Level 2 REAL version, and \texttt{sblat3.out} for the Level 3 REAL
+version, with similar names for the other data types.
+
+If the tests using the supplied data files were completed successfully,
+consider whether the tests were sufficiently thorough.
+For example, on a machine with vector registers, at least one value
+of $N$ greater than the length of the vector registers should be used;
+otherwise, important parts of the compiled code may not be
+exercised by the tests.
+If the tests were not successful, either because the program did not
+finish or the test ratios did not pass the threshold, you will
+probably have to find and correct the problem before continuing.
+If you have been testing a system-specific
+BLAS library, try using the Fortran BLAS for the routines that
+did not pass the tests.
+For more details on the BLAS test programs,
+see \cite{BLAS2-test} and \cite{BLAS3-test}.
+
+\subsection{Create the LAPACK Library}
+
+\begin{itemize}
+\item[a)]
+Go to the directory \texttt{LAPACK} and edit the definition of
+\texttt{lapacklib} in the file \texttt{Makefile} to specify the data types desired,
+as in the example in Section~\ref{toplevelmakefile}.
+
+\item[b)]
+Type \texttt{make lapacklib}.
+The make command can be run more than once to add another
+data type to the library if necessary.
+
+\end{itemize}
+
+\noindent
+The LAPACK library is created in \texttt{LAPACK/lapack\_PLAT.a}, where
+\texttt{PLAT} is the user-defined architecture suffix specified in the file
+\texttt{LAPACK/make.inc}.
+
+\subsection{Create the Test Matrix Generator Library}
+
+\begin{itemize}
+\item[a)]
+Go to the directory \texttt{LAPACK} and edit the definition of \texttt{tmglib}
+in the file \texttt{Makefile} to specify the data types desired, as in the
+example in Section~\ref{toplevelmakefile}.
+
+\item[b)]
+Type \texttt{make tmglib}.
+The make command can be run more than once to add another
+data type to the library if necessary.
+
+\end{itemize}
+
+\noindent
+The test matrix generator library is created in \texttt{LAPACK/tmglib\_PLAT.a},
+where \texttt{PLAT} is the user-defined architecture suffix specified in the
+file \texttt{LAPACK/make.inc}.
+
+\subsection{Run the LAPACK Test Programs}
+
+There are two distinct test programs for LAPACK routines
+in each data type, one for the linear equation routines and
+one for the eigensystem routines.
+In each data type, there is one input file for testing the linear
+equation routines and eighteen input files for testing the eigenvalue
+routines.
+The input files reside in \texttt{LAPACK/TESTING}.
+For more information on the test programs and how to modify the
+input files, please refer to LAPACK Working Note 41~\cite{WN41}.
+% see Section~\ref{moretesting}.
+
+If you do not wish to run each of the tests individually, you can
+go to \texttt{LAPACK}, edit the definition \texttt{lapack\_testing} in the file
+\texttt{Makefile} to specify the data types desired, and type \texttt{make
+lapack\_testing}. This will
+compile and run the tests as described in sections~\ref{testlin}
+and ~\ref{testeig}.
+
+%If you are installing LAPACK on a Silicon Graphics machine, you must
+%modify the definition of \texttt{testing} to be
+%\begin{verbatim}
+%testing:
+% ( cd TESTING; $(MAKE) -f Makefile.sgi )
+%\end{verbatim}
+
+\subsubsection{Testing the Linear Equations Routines}\label{testlin}
+
+\begin{itemize}
+
+\item[a)]
+Go to \texttt{LAPACK/TESTING/LIN} and type \texttt{make} followed by the data types
+desired. The executable files are called \texttt{xlintsts, xlintstc,
+xlintstd}, or \texttt{xlintstz} and are created in \texttt{LAPACK/TESTING}.
+
+\item[b)]
+Go to \texttt{LAPACK/TESTING} and run the tests for each data type.
+For the REAL version, the command is
+\begin{list}{}{}
+\item{} \texttt{xlintsts < stest.in > stest.out}
+\end{list}
+
+\noindent
+The tests using \texttt{xlintstd}, \texttt{xlintstc}, and \texttt{xlintstz} are similar
+with the leading `s' in the input and output file names replaced
+by `d', `c', or `z'.
+
+\end{itemize}
+
+If you encountered failures in this phase of the testing process, please
+refer to Section~\ref{sendresults}.
+
+\subsubsection{Testing the Eigensystem Routines}\label{testeig}
+
+\begin{itemize}
+
+\item[a)]
+Go to \texttt{LAPACK/TESTING/EIG} and type \texttt{make} followed by the data types
+desired. The executable files are called \texttt{xeigtsts,
+xeigtstc, xeigtstd}, and \texttt{xeigtstz} and are created
+in \texttt{LAPACK/TESTING}.
+
+\item[b)]
+Go to \texttt{LAPACK/TESTING} and run the tests for each data type.
+The tests for the eigensystem routines use eighteen separate input files
+for testing the nonsymmetric eigenvalue problem,
+the symmetric eigenvalue problem, the banded symmetric eigenvalue
+problem, the generalized symmetric eigenvalue
+problem, the generalized nonsymmetric eigenvalue problem, the
+singular value decomposition, the banded singular value decomposition,
+the generalized singular value
+decomposition, the generalized QR and RQ factorizations, the generalized
+linear regression model, and the constrained linear least squares
+problem.
+The tests for the REAL version are as follows:
+\begin{list}{}{}
+\item \texttt{xeigtsts < nep.in > snep.out}
+\item \texttt{xeigtsts < sep.in > ssep.out}
+\item \texttt{xeigtsts < svd.in > ssvd.out}
+\item \texttt{xeigtsts < sec.in > sec.out}
+\item \texttt{xeigtsts < sed.in > sed.out}
+\item \texttt{xeigtsts < sgg.in > sgg.out}
+\item \texttt{xeigtsts < sgd.in > sgd.out}
+\item \texttt{xeigtsts < ssg.in > ssg.out}
+\item \texttt{xeigtsts < ssb.in > ssb.out}
+\item \texttt{xeigtsts < sbb.in > sbb.out}
+\item \texttt{xeigtsts < sbal.in > sbal.out}
+\item \texttt{xeigtsts < sbak.in > sbak.out}
+\item \texttt{xeigtsts < sgbal.in > sgbal.out}
+\item \texttt{xeigtsts < sgbak.in > sgbak.out}
+\item \texttt{xeigtsts < glm.in > sglm.out}
+\item \texttt{xeigtsts < gqr.in > sgqr.out}
+\item \texttt{xeigtsts < gsv.in > sgsv.out}
+\item \texttt{xeigtsts < lse.in > slse.out}
+\end{list}
+The tests using \texttt{xeigtstc}, \texttt{xeigtstd}, and \texttt{xeigtstz} also
+use the input files \texttt{nep.in}, \texttt{sep.in}, \texttt{svd.in},
+\texttt{glm.in}, \texttt{gqr.in}, \texttt{gsv.in}, and \texttt{lse.in},
+but the leading `s' in the other input file names must be changed
+to `c', `d', or `z'.
+\end{itemize}
+
+If you encountered failures in this phase of the testing process, please
+refer to Section~\ref{sendresults}.
+
+\subsection{Run the LAPACK Timing Programs (For LAPACK 3.0 and before)}
+
+There are two distinct timing programs for LAPACK routines
+in each data type, one for the linear equation routines and
+one for the eigensystem routines. The timing program for the
+linear equation routines is also used to time the BLAS.
+We encourage you to conduct these timing experiments
+in REAL and COMPLEX or in DOUBLE PRECISION and COMPLEX*16; it is
+not necessary to send timing results in all four data types.
+
+Two sets of input files are provided, a small set and a large set.
+The small data sets are appropriate for a standard workstation or
+other non-vector machine.
+The large data sets are appropriate for supercomputers, vector
+computers, and high-performance workstations.
+We are mainly interested in results from the large data sets, and
+it is not necessary to run both the large and small sets.
+The values of N in the large data sets are about five times larger
+than those in the small data set,
+and the large data sets use additional values for parameters such as the
+block size NB and the leading array dimension LDA.
+Small data sets finished with the \_small in their name , such as
+\texttt{stime\_small.in}, and large data sets finished with \_large in their name,
+such as \texttt{stime\_large.in}.
+Except as noted, the leading `s' in the input file name must be
+replaced by `d', `c', or `z' for the other data types.
+
+We encourage you to obtain timing results with the large data sets,
+as this allows us to compare different machines.
+If this would take too much time, suggestions for paring back the large
+data sets are given in the instructions below.
+We also encourage you to experiment with these timing
+programs and send us any interesting results, such as results for
+larger problems or for a wider range of block sizes.
+The main programs are dimensioned for the large data sets,
+so the parameters in the main program may have to be reduced in order
+to run the small data sets on a small machine, or increased to run
+experiments with larger problems.
+
+The minimum time each subroutine will be timed is set to 0.0 in
+the large data files and to 0.05 in the small data files, and on
+many machines this value should be increased.
+If the timing interval is not long
+enough, the time for the subroutine after subtracting the overhead
+may be very small or zero, resulting in megaflop rates that are
+very large or zero. (To avoid division by zero, the megaflop rate is
+set to zero if the time is less than or equal to zero.)
+The minimum time that should be used depends on the machine and the
+resolution of the clock.
+
+For more information on the timing programs and how to modify the
+input files, please refer to LAPACK Working Note 41~\cite{WN41}.
+% see Section~\ref{moretiming}.
+
+If you do not wish to run each of the timings individually, you can
+go to \texttt{LAPACK}, edit the definition \texttt{lapack\_timing} in the file
+\texttt{Makefile} to specify the data types desired, and type \texttt{make
+lapack\_timing}. This will compile
+and run the timings for the linear equation routines and the eigensystem
+routines (see Sections~\ref{timelin} and ~\ref{timeeig}).
+
+%If you are installing LAPACK on a Silicon Graphics machine, you must
+%modify the definition of \texttt{timing} to be
+%\begin{verbatim}
+%timing:
+% ( cd TIMING; $(MAKE) -f Makefile.sgi )
+%\end{verbatim}
+
+If you encounter failures in any phase of the timing process, please
+feel free to contact the authors as directed in Section~\ref{sendresults}.
+Tell us the
+type of machine on which the tests were run, the version of the operating
+system, the compiler and compiler options that were used,
+and details of the BLAS library or libraries that you used. You should
+also include a copy of the output file in which the failure occurs.
+
+Please note that the BLAS
+timing runs will still need to be run as instructed in ~\ref{timeblas}.
+
+\subsubsection{Timing the Linear Equations Routines}\label{timelin}
+
+The linear equation timing program is found in \texttt{LAPACK/TIMING/LIN}
+and the input files are in \texttt{LAPACK/TIMING}.
+Three input files are provided in each data type for timing the
+linear equation routines, one for square matrices, one for band
+matrices, and one for rectangular matrices. The small data sets for the REAL version
+are \texttt{stime\_small.in}, \texttt{sband\_small.in}, and \texttt{stime2\_small.in}, respectively,
+and the large data sets are
+\texttt{stime\_large.in}, \texttt{sband\_large.in}, and \texttt{stime2\_large.in}.
+
+The timing program for the least squares routines uses special instrumented
+versions of the LAPACK routines to time individual sections of the code.
+The first step in compiling the timing program is therefore to make a library
+of the instrumented routines.
+
+\begin{itemize}
+\item[a)]
+\begin{sloppypar}
+To make a library of the instrumented LAPACK routines, first
+go to \texttt{LAPACK/TIMING/LIN/LINSRC} and type \texttt{make} followed
+by the data types desired, as in the examples of Section~\ref{toplevelmakefile}.
+The library of instrumented code is created in
+\texttt{LAPACK/TIMING/LIN/linsrc\_PLAT.a},
+where \texttt{PLAT} is the user-defined architecture suffix specified in the
+file \texttt{LAPACK/make.inc}.
+\end{sloppypar}
+
+\item[b)]
+To make the linear equation timing programs,
+go to \texttt{LAPACK/TIMING/LIN} and type \texttt{make} followed by the data
+types desired, as in the examples in Section~\ref{toplevelmakefile}.
+The executable files are called \texttt{xlintims},
+\texttt{xlintimc}, \texttt{xlintimd}, and \texttt{xlintimz} and are created
+in \texttt{LAPACK/TIMING}.
+
+\item[c)]
+Go to \texttt{LAPACK/TIMING} and
+make any necessary modifications to the input files.
+You may need to set the minimum time a subroutine will
+be timed to a positive value, or to restrict the size of the tests
+if you are using a computer with performance in between that of a
+workstation and that of a supercomputer.
+The computational requirements can be cut in half by using only one
+value of LDA.
+If it is necessary to also reduce the matrix sizes or the values of
+the blocksize, corresponding changes should be made to the
+BLAS input files (see Section~\ref{timeblas}).
+
+\item[d)]
+Run the programs for each data type you are using.
+For the REAL version, the commands for the small data sets are
+
+\begin{list}{}{}
+\item{} \texttt{xlintims < stime\_small.in > stime\_small.out }
+\item{} \texttt{xlintims < sband\_small.in > sband\_small.out }
+\item{} \texttt{xlintims < stime2\_small.in > stime2\_small.out }
+\end{list}
+or the commands for the large data sets are
+\begin{list}{}{}
+\item{} \texttt{xlintims < stime\_large.in > stime\_large.out }
+\item{} \texttt{xlintims < sband\_large.in > sband\_large.out }
+\item{} \texttt{xlintims < stime2\_large.in > stime2\_large.out }
+\end{list}
+
+\noindent
+Similar commands should be used for the other data types.
+\end{itemize}
+
+\subsubsection{Timing the BLAS}\label{timeblas}
+
+The linear equation timing program is also used to time the BLAS.
+Three input files are provided in each data type for timing the Level
+2 and 3 BLAS.
+These input files time the BLAS using the matrix shapes encountered
+in the LAPACK routines, and we will use the results to analyze the
+performance of the LAPACK routines.
+For the REAL version, the small data files are
+\texttt{sblasa\_small.in}, \texttt{sblasb\_small.in}, and \texttt{sblasc\_small.in}
+and the large data files are
+\texttt{sblasa\_large.in}, \texttt{sblasb\_large.in}, and \texttt{sblasc\_large.in}.
+There are three sets of inputs because there are three
+parameters in the Level 3 BLAS, M, N, and K, and
+in most applications one of these parameters is small (on the order
+of the blocksize) while the other two are large (on the order of the
+matrix size).
+In \texttt{sblasa\_small.in}, M and N are large but K is
+small, while in \texttt{sblasb\_small.in} the small parameter is M, and
+in \texttt{sblasc\_small.in} the small parameter is N.
+The Level 2 BLAS are timed only in the first data set, where K
+is also used as the bandwidth for the banded routines.
+
+\begin{itemize}
+
+\item[a)]
+Go to \texttt{LAPACK/TIMING} and
+make any necessary modifications to the input files.
+You may need to set the minimum time a subroutine will
+be timed to a positive value.
+If you modified the values of N or NB
+in Section~\ref{timelin}, set M, N, and K accordingly.
+The large parameters among M, N, and K
+should be the same as the matrix sizes used in timing the linear
+equation routines,
+and the small parameter should be the same as the
+blocksizes used in timing the linear equation routines.
+If necessary, the large data set can be simplified by using only one
+value of LDA.
+
+\item[b)]
+Run the programs for each data type you are using.
+For the REAL version, the commands for the small data sets are
+
+\begin{list}{}{}
+\item{} \texttt{xlintims < sblasa\_small.in > sblasa\_small.out }
+\item{} \texttt{xlintims < sblasb\_small.in > sblasb\_small.out }
+\item{} \texttt{xlintims < sblasc\_small.in > sblasc\_small.out }
+\end{list}
+or the commands for the large data sets are
+\begin{list}{}{}
+\item{} \texttt{xlintims < sblasa\_large.in > sblasa\_large.out }
+\item{} \texttt{xlintims < sblasb\_large.in > sblasb\_large.out }
+\item{} \texttt{xlintims < sblasc\_large.in > sblasc\_large.out }
+\end{list}
+
+\noindent
+Similar commands should be used for the other data types.
+\end{itemize}
+
+\subsubsection{Timing the Eigensystem Routines}\label{timeeig}
+
+The eigensystem timing program is found in \texttt{LAPACK/TIMING/EIG}
+and the input files are in \texttt{LAPACK/TIMING}.
+Four input files are provided in each data type for timing the
+eigensystem routines,
+one for the generalized nonsymmetric eigenvalue problem,
+one for the nonsymmetric eigenvalue problem,
+one for the symmetric and generalized symmetric eigenvalue problem,
+and one for the singular value decomposition.
+For the REAL version, the small data sets are called \texttt{sgeptim\_small.in},
+\texttt{sneptim\_small.in}, \texttt{sseptim\_small.in}, and \texttt{ssvdtim\_small.in}, respectively.
+and the large data sets are called \texttt{sgeptim\_large.in}, \texttt{sneptim\_large.in},
+\texttt{sseptim\_large.in}, and \texttt{ssvdtim\_large.in}.
+Each of the four input files reads a different set of parameters,
+and the format of the input is indicated by a 3-character code
+on the first line.
+
+The timing program for eigenvalue/singular value routines accumulates
+the operation count as the routines are executing using special
+instrumented versions of the LAPACK routines. The first step in
+compiling the timing program is therefore to make a library of the
+instrumented routines.
+
+\begin{itemize}
+\item[a)]
+\begin{sloppypar}
+To make a library of the instrumented LAPACK routines, first
+go to \texttt{LAPACK/TIMING/EIG/EIGSRC} and type \texttt{make} followed
+by the data types desired, as in the examples of Section~\ref{toplevelmakefile}.
+The library of instrumented code is created in
+\texttt{LAPACK/TIMING/EIG/eigsrc\_PLAT.a},
+where \texttt{PLAT} is the user-defined architecture suffix specified in the
+file \texttt{LAPACK/make.inc}.
+\end{sloppypar}
+
+\item[b)]
+To make the eigensystem timing programs,
+go to \texttt{LAPACK/TIMING/EIG} and
+type \texttt{make} followed by the data types desired, as in the examples
+of Section~\ref{toplevelmakefile}. The executable files are called
+\texttt{xeigtims}, \texttt{xeigtimc}, \texttt{xeigtimd}, and \texttt{xeigtimz}
+and are created in \texttt{LAPACK/TIMING}.
+
+\item[c)]
+Go to \texttt{LAPACK/TIMING} and
+make any necessary modifications to the input files.
+You may need to set the minimum time a subroutine will
+be timed to a positive value, or to restrict the number of tests
+if you are using a computer with performance in between that of a
+workstation and that of a supercomputer.
+Instead of decreasing the matrix dimensions to reduce the time,
+it would be better to reduce the number of matrix types to be timed,
+since the performance varies more with the matrix size than with the
+type. For example, for the nonsymmetric eigenvalue routines,
+you could use only one matrix of type 4 instead of four matrices of
+types 1, 3, 4, and 6.
+Refer to LAPACK Working Note 41~\cite{WN41} for further details.
+% See Section~\ref{moretiming} for further details.
+
+\item[d)]
+Run the programs for each data type you are using.
+For the REAL version, the commands for the small data sets are
+
+\begin{list}{}{}
+\item{} \texttt{xeigtims < sgeptim\_small.in > sgeptim\_small.out }
+\item{} \texttt{xeigtims < sneptim\_small.in > sneptim\_small.out }
+\item{} \texttt{xeigtims < sseptim\_small.in > sseptim\_small.out }
+\item{} \texttt{xeigtims < ssvdtim\_small.in > ssvdtim\_small.out }
+\end{list}
+or the commands for the large data sets are
+\begin{list}{}{}
+\item{} \texttt{xeigtims < sgeptim\_large.in > sgeptim\_large.out }
+\item{} \texttt{xeigtims < sneptim\_large.in > sneptim\_large.out }
+\item{} \texttt{xeigtims < sseptim\_large.in > sseptim\_large.out }
+\item{} \texttt{xeigtims < ssvdtim\_large.in > ssvdtim\_large.out }
+\end{list}
+
+\noindent
+Similar commands should be used for the other data types.
+\end{itemize}
+
+\subsection{Send the Results to Tennessee}\label{sendresults}
+
+Congratulations! You have now finished installing, testing, and
+timing LAPACK. If you encountered failures in any phase of the
+testing or timing process, please
+consult our \texttt{release\_notes} file on netlib.
+\begin{quote}
+\url{http://www.netlib.org/lapack/release\_notes}
+\end{quote}
+This file contains machine-dependent installation clues which hopefully will
+alleviate your difficulties or at least let you know that other users
+have had similar difficulties on that machine. If there is not an entry
+for your machine or the suggestions do not fix your problem, please feel
+free to contact the authors at
+\begin{list}{}{}
+\item \href{mailto:lapack@cs.utk.edu}{\texttt{lapack@cs.utk.edu}}.
+\end{list}
+Tell us the
+type of machine on which the tests were run, the version of the operating
+system, the compiler and compiler options that were used,
+and details of the BLAS library or libraries that you used. You should
+also include a copy of the output file in which the failure occurs.
+
+We would like to keep our \texttt{release\_notes} file as up-to-date as possible.
+Therefore, if you do not see an entry for your machine, please contact us
+with your testing results.
+
+Comments and suggestions are also welcome.
+
+We encourage you to make the LAPACK library available to your
+users and provide us with feedback from their experiences.
+%This release of LAPACK is not guaranteed to be compatible
+%with any previous test release.
+
+\subsection{Get support}\label{getsupport}
+First, take a look at the complete installation manual in the LAPACK Working Note 41~\cite{WN41}.
+if you still cannot solve your problem, you have 2 ways to go:
+\begin{itemize}
+\item
+either send a post in the LAPACK forum
+\begin{quote}
+\url{http://icl.cs.utk.edu/lapack-forum}
+\end{quote}
+\item
+or send an email to the LAPACK mailing list:
+\begin{list}{}{}
+\item \href{mailto:lapack@cs.utk.edu}{\texttt{lapack@cs.utk.edu}}.
+\end{list}
+\end{itemize}
+\section*{Acknowledgments}
+
+Ed Anderson and Susan Blackford contributed to previous versions of this report.
+
+\appendix
+
+\chapter{Caveats}\label{appendixd}
+
+In this appendix we list a few of the machine-specific difficulties we
+have
+encountered in our own experience with LAPACK. A more detailed list
+of machine-dependent problems, bugs, and compiler errors encountered
+in the LAPACK installation process is maintained
+on \emph{netlib}.
+\begin{quote}
+\url{http://www.netlib.org/lapack/release\_notes}
+\end{quote}
+
+We assume the user has installed the machine-specific routines
+correctly and that the Level 1, 2 and 3 BLAS test programs have run
+successfully, so we do not list any warnings associated with those
+routines.
+
+\section{\texttt{LAPACK/make.inc}}
+
+All machine-specific
+parameters are specified in the file \texttt{LAPACK/make.inc}.
+
+The first line of this \texttt{make.inc} file is:
+\begin{quote}
+SHELL = /bin/sh
+\end{quote}
+and will need to be modified to \texttt{SHELL = /sbin/sh} if you are
+installing LAPACK on an SGI architecture.
+
+\section{ETIME}
+
+On HPPA architectures,
+the compiler and loader flag \texttt{+U77} should be included to access
+the function \texttt{ETIME}.
+
+\section{ILAENV and IEEE-754 compliance}
+
+%By default, ILAENV (\texttt{LAPACK/SRC/ilaenv.f}) assumes an IEEE and IEEE-754
+%compliant architecture, and thus sets (\texttt{ILAENV=1}) for (\texttt{ISPEC=10})
+%and (\texttt{ISPEC=11}) settings in ILAENV.
+%
+%If you are installing LAPACK on a non-IEEE machine, you MUST modify ILAENV,
+%as this test inside ILAENV will crash!
+
+As some new routines in LAPACK rely on IEEE-754 compliance,
+two settings (\texttt{ISPEC=10} and \texttt{ISPEC=11}) have been added to ILAENV
+(\texttt{LAPACK/SRC/ilaenv.f}) to denote IEEE-754 compliance for NaN and
+infinity arithmetic, respectively. By default, ILAENV assumes an IEEE
+machine, and does a test for IEEE-754 compliance. \textbf{NOTE: If you
+are installing LAPACK on a non-IEEE machine, you MUST modify ILAENV,
+as this test inside ILAENV will crash!}
+
+Thus, for non-IEEE machines, the user must hard-code the setting of
+(\texttt{ILAENV=0}) for (\texttt{ISPEC=10} and \texttt{ISPEC=11}) in the version
+of \texttt{LAPACK/SRC/ilaenv.f} to be put in
+his library. For further details, refer to section~\ref{testieee}.
+
+Be aware
+that some IEEE compilers by default do not enforce IEEE-754 compliance, and
+a compiler flag must be explicitly set by the user.
+
+On SGIs for example, you must set the \texttt{-OPT:IEEE\_NaN\_inf=ON} compiler
+flag to enable IEEE-754 compliance.
+
+And lastly, the test inside ILAENV to detect IEEE-754 compliance, will
+result in IEEE exceptions for ``Divide by Zero'' and ``Invalid Operation''.
+Thus, if the user is installing on a machine that issues IEEE exception
+warning messages (like a Sun SPARCstation), the user can disregard these
+messages. To avoid these messages, the user can hard-code the values
+inside ILAENV as explained in section~\ref{testieee}.
+
+\section{Lack of \texttt{/tmp} space}
+
+If \texttt{/tmp} space is small (i.e., less than approximately 16 MB) on your
+architecture, you may run out of space
+when compiling. There are a few possible solutions to this problem.
+\begin{enumerate}
+\item You can ask your system administrator to increase the size of the
+\texttt{/tmp} partition.
+\item You can change the environment variable \texttt{TMPDIR} to point to
+your home directory for temporary space. E.g.,
+\begin{quote}
+\texttt{setenv TMPDIR /home/userid/}
+\end{quote}
+where \texttt{/home/userid/} is the user's home directory.
+\item If your archive command has an \texttt{l} option, you can change the
+archive command to \texttt{ar crl} so that the
+archive command will only place temporary files in the current working
+directory rather than in the default temporary directory /tmp.
+\end{enumerate}
+
+\section{BLAS}
+
+If you suspect a BLAS-related problem and you are linking
+with an optimized version of the BLAS, we would strongly suggest
+as a first step that you link to the Fortran 77 version of
+the suspected BLAS routine and see if the error has disappeared.
+
+We have included test programs for the Level 1 BLAS.
+Users should therefore beware of a common problem in machine-specific
+implementations of xNRM2,
+the function to compute the 2-norm of a vector.
+The Fortran version of xNRM2 avoids underflow or overflow
+by scaling intermediate results, but some library versions of xNRM2
+are not so careful about scaling.
+If xNRM2 is implemented without scaling intermediate results, some of
+the LAPACK test ratios may be unusually high, or
+a floating point exception may occur in the problems scaled near
+underflow or overflow.
+The solution to these problems is to link the Fortran version of
+xNRM2 with the test program. \emph{On some CRAY architectures, the Fortran77
+version of xNRM2 should be used.}
+
+\section{Optimization}
+
+If a large numbers of test failures occur for a specific matrix type
+or operation, it could be that there is an optimization problem with
+your compiler. Thus, the user could try reducing the level of
+optimization or eliminating optimization entirely for those routines
+to see if the failures disappear when you rerun the tests.
+
+%LAPACK is written in Fortran 77. Prospective users with only a
+%Fortran 66 compiler will not be able to use this package.
+
+\section{Compiling testing/timing drivers}
+
+The testing and timing main programs (xCHKAA, xCHKEE, xTIMAA, and
+xTIMEE)
+allocate large amounts of local variables. Therefore, it is vitally
+important that the user know if his compiler by default allocates local
+variables statically or on the stack. It is not uncommon for those
+compilers which place local variables on the stack to cause a stack
+overflow at runtime in the testing or timing process. The user then
+has two options: increase your stack size, or force all local variables
+to be allocated statically.
+
+On HPPA architectures, the
+compiler and loader flag \texttt{-K} should be used when compiling these testing
+and timing main programs to avoid such a stack overflow. I.e., set
+\texttt{DRVOPTS = -K} in the \texttt{LAPACK/make.inc} file.
+
+For similar reasons,
+on SGI architectures, the compiler and loader flag \texttt{-static} should be
+used. I.e., set \texttt{DRVOPTS = -static} in the \texttt{LAPACK/make.inc} file.
+
+\section{IEEE arithmetic}
+
+Some of our test matrices are scaled near overflow or underflow,
+but on the Crays, problems with the arithmetic near overflow and
+underflow forced us to scale by only the square root of overflow
+and underflow.
+The LAPACK auxiliary routine SLABAD (or DLABAD) is called to
+take the square root of underflow and overflow in cases where it
+could cause difficulties.
+We assume we are on a Cray if $ \log_{10} (\mathrm{overflow})$
+is greater than 2000
+and take the square root of underflow and overflow in this case.
+The test in SLABAD is as follows:
+\begin{verbatim}
+ IF( LOG10( LARGE ).GT.2000. ) THEN
+ SMALL = SQRT( SMALL )
+ LARGE = SQRT( LARGE )
+ END IF
+\end{verbatim}
+Users of other machines with similar restrictions on the effective
+range of usable numbers may have to modify this test so that the
+square roots are done on their machine as well. \emph{Usually on
+HPPA architectures, a similar restriction in SLABAD should be enforced
+for all testing involving complex arithmetic.}
+SLABAD is located in \texttt{LAPACK/SRC}.
+
+For machines which have a narrow exponent range or lack gradual
+underflow (DEC VAXes for example), it is not uncommon to experience
+failures in sec.out and/or dec.out with SLAQTR/DLAQTR or DTRSYL.
+The failures in SLAQTR/DLAQTR and DTRSYL
+occur with test problems which are very badly scaled when the norm of
+the solution is very close to the underflow
+threshold (or even underflows to zero). We believe that these failures
+could probably be avoided by an even greater degree of care in scaling,
+but we did not want to delay the release of LAPACK any further. These
+tests pass successfully on most other machines. An example failure in
+dec.out on a MicroVAX II looks like the following:
+
+\begin{verbatim}
+Tests of the Nonsymmetric eigenproblem condition estimation routines
+DLALN2, DLASY2, DLANV2, DLAEXC, DTRSYL, DTREXC, DTRSNA, DTRSEN, DLAQTR
+
+Relative machine precision (EPS) = 0.277556D-16
+Safe minimum (SFMIN) = 0.587747D-38
+
+Routines pass computational tests if test ratio is less than 20.00
+
+DEC routines passed the tests of the error exits ( 35 tests done)
+Error in DTRSYL: RMAX = 0.155D+07
+LMAX = 5323 NINFO= 1600 KNT= 27648
+Error in DLAQTR: RMAX = 0.344D+04
+LMAX = 15792 NINFO= 26720 KNT= 45000
+\end{verbatim}
+
+\section{Timing programs}
+
+In the eigensystem timing program, calls are made to the LINPACK
+and EISPACK equivalents of the LAPACK routines to allow a direct
+comparison of performance measures.
+In some cases we have increased the minimum number of
+iterations in the LINPACK and EISPACK routines to allow
+them to converge for our test problems, but
+even this may not be enough.
+One goal of the LAPACK project is to improve the convergence
+properties of these routines, so error messages in the output
+file indicating that a LINPACK or EISPACK routine did not
+converge should not be regarded with alarm.
+
+In the eigensystem timing program, we have equivalenced some work
+arrays and then passed them to a subroutine, where both arrays are
+modified. This is a violation of the Fortran 77 standard, which
+says ``if a subprogram reference causes a dummy argument in the
+referenced subprogram to become associated with another dummy
+argument in the referenced subprogram, neither dummy argument may
+become defined during execution of the subprogram.''
+\footnote{ ANSI X3.9-1978, sec. 15.9.3.6}
+If this causes any difficulties, the equivalence
+can be commented out as explained in the comments for the main
+eigensystem timing programs.
+
+%\section*{MACHINE-SPECIFIC DIFFICULTIES}
+%Some IBM compilers do not recognize DBLE as a generic function as used
+%in LAPACK. The software tools we use to convert from single precision
+%to double precision convert REAL(C) and AIMAG(C), where C is COMPLEX,
+%to DBLE(Z) and DIMAG(Z), where Z is COMPLEX*16, but
+%IBM compilers use DREAL(Z) and DIMAG(Z) to take the real and
+%imaginary parts of a double complex number.
+%IBM users can fix this problem by changing DBLE to DREAL when the
+%argument of DBLE is COMPLEX*16.
+%
+%IBM compilers do not permit the data type COMPLEX*16 in a FUNCTION
+%subprogram definition. The data type on the first line of the
+%function subprogram must be changed from COMPLEX*16 to DOUBLE COMPLEX
+%for the following functions:
+%
+%\begin{tabbing}
+%\dent ZLATMOO \= from the test matrix generator library \kill
+%\dent ZBEG \> from the Level 2 BLAS test program \\
+%\dent ZBEG \> from the Level 3 BLAS test program \\
+%\dent ZLADIV \> from the LAPACK library \\
+%\dent ZLARND \> from the test matrix generator library \\
+%\dent ZLATM2 \> from the test matrix generator library \\
+%\dent ZLATM3 \> from the test matrix generator library
+%\end{tabbing}
+%The functions ZDOTC and ZDOTU from the Level 1 BLAS are already
+%declared DOUBLE COMPLEX. If that doesn't work, try the declaration
+%COMPLEX FUNCTION*16.
+
+
+\newpage
+\addcontentsline{toc}{section}{Bibliography}
+
+\begin{thebibliography}{9}
+
+\bibitem{LUG}
+E. Anderson, Z. Bai, C. Bischof, J. Demmel, J. Dongarra,
+J. Du Croz, A. Greenbaum, S. Hammarling, A. McKenney,
+S. Ostrouchov, and D. Sorensen,
+\textit{LAPACK Users' Guide}, Second Edition,
+{SIAM}, Philadelphia, PA, 1995.
+
+\bibitem{WN16}
+E. Anderson and J. Dongarra,
+\textit{LAPACK Working Note 16:
+Results from the Initial Release of LAPACK},
+University of Tennessee, CS-89-89, November 1989.
+
+\bibitem{WN41}
+E. Anderson, J. Dongarra, and S. Ostrouchov,
+\textit{LAPACK Working Note 41:
+Installation Guide for LAPACK},
+University of Tennessee, CS-92-151, February 1992 (revised June 1999).
+
+\bibitem{WN5}
+C. Bischof, J. Demmel, J. Dongarra, J. Du Croz, A. Greenbaum,
+S. Hammarling, and D. Sorensen,
+\textit{LAPACK Working Note \#5: Provisional Contents},
+Argonne National Laboratory, ANL-88-38, September 1988.
+
+\bibitem{WN13}
+Z. Bai, J. Demmel, and A. McKenney,
+\textit{LAPACK Working Note \#13: On the Conditioning of the Nonsymmetric
+Eigenvalue Problem: Theory and Software},
+University of Tennessee, CS-89-86, October 1989.
+
+\bibitem{BLAS3}
+J. Dongarra, J. Du Croz, I. Duff, and S. Hammarling,
+``A Set of Level 3 Basic Linear Algebra Subprograms,''
+\textit{ACM Trans. Math. Soft.}, 16, 1:1-17, March 1990
+%Argonne National Laboratory, ANL-MCS-P88-1, August 1988.
+
+\bibitem{BLAS3-test}
+J. Dongarra, J. Du Croz, I. Duff, and S. Hammarling,
+``A Set of Level 3 Basic Linear Algebra Subprograms:
+Model Implementation and Test Programs,''
+\textit{ACM Trans. Math. Soft.}, 16, 1:18-28, March 1990
+%Argonne National Laboratory, ANL-MCS-TM-119, June 1988.
+
+\bibitem{BLAS2}
+J. Dongarra, J. Du Croz, S. Hammarling, and R. Hanson,
+``An Extended Set of Fortran Basic Linear Algebra Subprograms,''
+\textit{ACM Trans. Math. Soft.}, 14, 1:1-17, March 1988.
+
+\bibitem{BLAS2-test}
+J. Dongarra, J. Du Croz, S. Hammarling, and R. Hanson,
+``An Extended Set of Fortran Basic Linear Algebra Subprograms:
+Model Implementation and Test Programs,''
+\textit{ACM Trans. Math. Soft.}, 14, 1:18-32, March 1988.
+
+\bibitem{BLAS1}
+C. L. Lawson, R. J. Hanson, D. R. Kincaid, and F. T. Krogh,
+``Basic Linear Algebra Subprograms for Fortran Usage,''
+\textit{ACM Trans. Math. Soft.}, 5, 3:308-323, September 1979.
+
+\end{thebibliography}
+
+\end{document}
diff --git a/INSTALL/lpk_gnumake.tar b/INSTALL/lpk_gnumake.tar
new file mode 100644
index 00000000..e745617b
--- /dev/null
+++ b/INSTALL/lpk_gnumake.tar
Binary files differ
diff --git a/INSTALL/lsame.f b/INSTALL/lsame.f
new file mode 100644
index 00000000..70551755
--- /dev/null
+++ b/INSTALL/lsame.f
@@ -0,0 +1,86 @@
+ LOGICAL FUNCTION LSAME( CA, CB )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ CHARACTER CA, CB
+* ..
+*
+* Purpose
+* =======
+*
+* LSAME returns .TRUE. if CA is the same letter as CB regardless of
+* case.
+*
+* Arguments
+* =========
+*
+* CA (input) CHARACTER*1
+* CB (input) CHARACTER*1
+* CA and CB specify the single characters to be compared.
+*
+* =====================================================================
+*
+* .. Intrinsic Functions ..
+ INTRINSIC ICHAR
+* ..
+* .. Local Scalars ..
+ INTEGER INTA, INTB, ZCODE
+* ..
+* .. Executable Statements ..
+*
+* Test if the characters are equal
+*
+ LSAME = CA.EQ.CB
+ IF( LSAME )
+ $ RETURN
+*
+* Now test for equivalence if both characters are alphabetic.
+*
+ ZCODE = ICHAR( 'Z' )
+*
+* Use 'Z' rather than 'A' so that ASCII can be detected on Prime
+* machines, on which ICHAR returns a value with bit 8 set.
+* ICHAR('A') on Prime machines returns 193 which is the same as
+* ICHAR('A') on an EBCDIC machine.
+*
+ INTA = ICHAR( CA )
+ INTB = ICHAR( CB )
+*
+ IF( ZCODE.EQ.90 .OR. ZCODE.EQ.122 ) THEN
+*
+* ASCII is assumed - ZCODE is the ASCII code of either lower or
+* upper case 'Z'.
+*
+ IF( INTA.GE.97 .AND. INTA.LE.122 ) INTA = INTA - 32
+ IF( INTB.GE.97 .AND. INTB.LE.122 ) INTB = INTB - 32
+*
+ ELSE IF( ZCODE.EQ.233 .OR. ZCODE.EQ.169 ) THEN
+*
+* EBCDIC is assumed - ZCODE is the EBCDIC code of either lower or
+* upper case 'Z'.
+*
+ IF( INTA.GE.129 .AND. INTA.LE.137 .OR.
+ $ INTA.GE.145 .AND. INTA.LE.153 .OR.
+ $ INTA.GE.162 .AND. INTA.LE.169 ) INTA = INTA + 64
+ IF( INTB.GE.129 .AND. INTB.LE.137 .OR.
+ $ INTB.GE.145 .AND. INTB.LE.153 .OR.
+ $ INTB.GE.162 .AND. INTB.LE.169 ) INTB = INTB + 64
+*
+ ELSE IF( ZCODE.EQ.218 .OR. ZCODE.EQ.250 ) THEN
+*
+* ASCII is assumed, on Prime machines - ZCODE is the ASCII code
+* plus 128 of either lower or upper case 'Z'.
+*
+ IF( INTA.GE.225 .AND. INTA.LE.250 ) INTA = INTA - 32
+ IF( INTB.GE.225 .AND. INTB.LE.250 ) INTB = INTB - 32
+ END IF
+ LSAME = INTA.EQ.INTB
+*
+* RETURN
+*
+* End of LSAME
+*
+ END
diff --git a/INSTALL/lsametst.f b/INSTALL/lsametst.f
new file mode 100644
index 00000000..ced21825
--- /dev/null
+++ b/INSTALL/lsametst.f
@@ -0,0 +1,60 @@
+ PROGRAM TEST1
+*
+* -- LAPACK test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Local Scalars ..
+ INTEGER I1, I2
+* ..
+* .. External Functions ..
+ LOGICAL LSAME
+ EXTERNAL LSAME
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC ICHAR
+* ..
+* .. Executable Statements ..
+*
+*
+* Determine the character set.
+*
+ I1 = ICHAR( 'A' )
+ I2 = ICHAR( 'a' )
+ IF( I2-I1.EQ.32 ) THEN
+ WRITE( *, * ) ' ASCII character set'
+ ELSE
+ WRITE( *, * ) ' Non-ASCII character set, IOFF should be ',I2-I1
+ END IF
+*
+* Test LSAME.
+*
+ IF( .NOT.LSAME( 'A', 'A' ) )
+ $ WRITE( *, 9999 )'A', 'A'
+ IF( .NOT.LSAME( 'A', 'a' ) )
+ $ WRITE( *, 9999 )'A', 'a'
+ IF( .NOT.LSAME( 'a', 'A' ) )
+ $ WRITE( *, 9999 )'a', 'A'
+ IF( .NOT.LSAME( 'a', 'a' ) )
+ $ WRITE( *, 9999 )'a', 'a'
+ IF( LSAME( 'A', 'B' ) )
+ $ WRITE( *, 9998 )'A', 'B'
+ IF( LSAME( 'A', 'b' ) )
+ $ WRITE( *, 9998 )'A', 'b'
+ IF( LSAME( 'a', 'B' ) )
+ $ WRITE( *, 9998 )'a', 'B'
+ IF( LSAME( 'a', 'b' ) )
+ $ WRITE( *, 9998 )'a', 'b'
+ IF( LSAME( 'O', '/' ) )
+ $ WRITE( *, 9998 )'O', '/'
+ IF( LSAME( '/', 'O' ) )
+ $ WRITE( *, 9998 )'/', 'O'
+ IF( LSAME( 'o', '/' ) )
+ $ WRITE( *, 9998 )'o', '/'
+ IF( LSAME( '/', 'o' ) )
+ $ WRITE( *, 9998 )'/', 'o'
+ WRITE( *, * )' Tests completed'
+*
+ 9999 FORMAT( ' *** Error: LSAME( ', A1, ', ', A1, ') is .FALSE.' )
+ 9998 FORMAT( ' *** Error: LSAME( ', A1, ', ', A1, ') is .TRUE.' )
+ END
diff --git a/INSTALL/make.inc.ALPHA b/INSTALL/make.inc.ALPHA
new file mode 100644
index 00000000..e7d28ac4
--- /dev/null
+++ b/INSTALL/make.inc.ALPHA
@@ -0,0 +1,69 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _ALPHA
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = f77
+OPTS = -O4 -fpe1
+DRVOPTS = $(OPTS)
+NOOPT =
+LOADER = f77
+LOADOPTS =
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = cc
+CFLAGS = -O3
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = ranlib
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+#BLASLIB = ../../blas$(PLAT).a
+BLASLIB = -ldxml
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.HPPA b/INSTALL/make.inc.HPPA
new file mode 100644
index 00000000..9770b859
--- /dev/null
+++ b/INSTALL/make.inc.HPPA
@@ -0,0 +1,69 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _HPPA
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = f77
+OPTS = +O4 +U77
+DRVOPTS = $(OPTS) -K
+NOOPT = +U77
+LOADER = f77
+LOADOPTS = -Aa +U77
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = cc
+CFLAGS = +O2 +DA2.0 +DS2.0
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = echo
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+#BLASLIB = ../../blas$(PLAT).a
+BLASLIB = -lblas
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.IRIX64 b/INSTALL/make.inc.IRIX64
new file mode 100644
index 00000000..2fd032f1
--- /dev/null
+++ b/INSTALL/make.inc.IRIX64
@@ -0,0 +1,72 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /sbin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _IRIX64-64
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = f77
+OPTS = -O3 -64 -mips4 -r10000 -OPT:IEEE_NaN_inf=ON
+#OPTS = -g -DEBUG:subscript_check=ON -trapuv -OPT:IEEE_NaN_inf=ON
+DRVOPTS = $(OPTS) -static
+NOOPT = -64 -mips4 -r10000 -OPT:IEEE_NaN_inf=ON
+#NOOPT = -g -DEBUG:subscript_check=ON -trapuv -OPT:IEEE_NaN_inf=ON
+LOADER = f77
+LOADOPTS = -O3 -64 -mips4 -r10000 -OPT:IEEE_NaN_inf=ON
+#LOADOPTS = -g -DEBUG:subscript_check=ON -trapuv -OPT:IEEE_NaN_inf=ON
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = cc
+CFLAGS = -O3 -64
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = echo
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+BLASLIB = ../../blas$(PLAT).a
+#BLASLIB = -lblas
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.LINUX b/INSTALL/make.inc.LINUX
new file mode 100644
index 00000000..5441f300
--- /dev/null
+++ b/INSTALL/make.inc.LINUX
@@ -0,0 +1,68 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _LINUX
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = g77
+OPTS = -funroll-all-loops -O3
+DRVOPTS = $(OPTS)
+NOOPT =
+LOADER = g77
+LOADOPTS =
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = gcc
+CFLAGS = -O3 -Dx86
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS = cr
+RANLIB = ranlib
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+BLASLIB = ../../blas$(PLAT).a
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.O2K b/INSTALL/make.inc.O2K
new file mode 100644
index 00000000..27eb5f5e
--- /dev/null
+++ b/INSTALL/make.inc.O2K
@@ -0,0 +1,74 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /sbin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _IRIX64
+#PLAT = _IRIX64mp
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = f77
+OPTS = -O3 -64 -mips4 -r10000
+#OPTS = -O3 -64 -mips4 -r10000 -mp
+DRVOPTS = $(OPTS) -static
+NOOPT = -64 -mips4 -r10000
+#NOOPT = -64 -mips4 -r10000 -mp
+LOADER = f77
+LOADOPTS = -O3 -64 -mips4 -r10000
+#LOADOPTS = -O3 -64 -mips4 -r10000 -mp
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = cc
+CFLAGS = -O3 -64
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = echo
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+BLASLIB = -lblas
+#BLASLIB = -lblas_mp
+#BLASLIB = ../../blas$(PLAT).a
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.RS6K b/INSTALL/make.inc.RS6K
new file mode 100644
index 00000000..a52d10c5
--- /dev/null
+++ b/INSTALL/make.inc.RS6K
@@ -0,0 +1,69 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _RS6K
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = xlf
+OPTS = -O3 -qmaxmem=-1
+DRVOPTS = $(OPTS)
+NOOPT =
+LOADER = xlf
+LOADOPTS =
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = xlc
+OPTS = -O2
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+#TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = ranlib
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+#BLASLIB = ../../blas$(PLAT).a
+BLASLIB = -lessl
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.SGI5 b/INSTALL/make.inc.SGI5
new file mode 100644
index 00000000..aa3e7dc4
--- /dev/null
+++ b/INSTALL/make.inc.SGI5
@@ -0,0 +1,69 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /sbin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _SGI5
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = f77
+OPTS = -O4
+DRVOPTS = $(OPTS) -static
+NOOPT =
+LOADER = f77
+LOADOPTS =
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = cc
+CFLAGS = -O3
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = echo
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+BLASLIB = ../../blas$(PLAT).a
+#BLASLIB = -lblas
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.SUN4 b/INSTALL/make.inc.SUN4
new file mode 100644
index 00000000..9e9aeceb
--- /dev/null
+++ b/INSTALL/make.inc.SUN4
@@ -0,0 +1,69 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _SUN4
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = f77
+OPTS = -dalign -O4 -fast
+DRVOPTS = $(OPTS)
+NOOPT =
+LOADER = f77
+LOADOPTS = -dalign -O4 -fast
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = cc
+CFLAGS = -O4
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = ranlib
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+BLASLIB = ../../blas$(PLAT).a
+#BLASLIB = -lblas
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.SUN4SOL2 b/INSTALL/make.inc.SUN4SOL2
new file mode 100644
index 00000000..7fa53e79
--- /dev/null
+++ b/INSTALL/make.inc.SUN4SOL2
@@ -0,0 +1,75 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _SUN4SOL2
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = f77
+#OPTS = -O4 -u -f -mt
+#OPTS = -u -f -dalign -native -xO5 -xarch=v8plusa
+OPTS = -u -f -dalign -native -xO2 -xarch=v8plusa
+DRVOPTS = $(OPTS)
+NOOPT = -u -f
+#NOOPT = -u -f -mt
+LOADER = f77
+# ADOPTS = -mt
+LOADOPTS = -f -dalign -native -xO2 -xarch=v8plusa
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = cc
+CFLAGS = -xO4
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+=======
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = echo
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+#BLASLIB = ../../blas$(PLAT).a
+#BLASLIB = -xlic_lib=sunperf_mt
+BLASLIB = -xlic_lib=sunperf
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.gfortran b/INSTALL/make.inc.gfortran
new file mode 100644
index 00000000..8b6b5704
--- /dev/null
+++ b/INSTALL/make.inc.gfortran
@@ -0,0 +1,68 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _LINUX
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = gfortran
+OPTS = -O2
+DRVOPTS = $(OPTS)
+NOOPT = -O0
+LOADER = gfortran
+LOADOPTS =
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = gcc
+CFLAGS = -O3 -Dx86
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+#TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = ranlib
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+BLASLIB = ../../blas$(PLAT).a
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/make.inc.pghpf b/INSTALL/make.inc.pghpf
new file mode 100644
index 00000000..dafd1785
--- /dev/null
+++ b/INSTALL/make.inc.pghpf
@@ -0,0 +1,69 @@
+####################################################################
+# LAPACK make include file. #
+# LAPACK, Version 3.1.1 #
+# February 2007 #
+####################################################################
+#
+SHELL = /bin/sh
+#
+# The machine (platform) identifier to append to the library names
+#
+PLAT = _pghpf_SUNMP
+#
+# Modify the FORTRAN and OPTS definitions to refer to the
+# compiler and desired compiler options for your machine. NOOPT
+# refers to the compiler options desired when NO OPTIMIZATION is
+# selected. Define LOADER and LOADOPTS to refer to the loader and
+# desired load options for your machine.
+#
+FORTRAN = pghpf
+OPTS = -O4 -Mnohpfc -Mdclchk
+DRVOPTS = $(OPTS)
+NOOPT = -Mnohpfc -Mdclchk
+LOADER = pghpf
+LOADOPTS =
+#
+# For XBLAS library
+# Modify the CC and CFLAGS definitions to refer to the
+# compiler and desired compiler options for your machine.
+# Define LINKER and LINKOPTS to refer to the loader and
+# desired load options for your machine.
+#
+CC = pgcc
+CFLAGS = -O4
+LINKER = $(CC)
+LDFLAGS =
+EXTRA_LIBS = -lm
+#
+# Timer for the SECOND and DSECND routines
+#
+# Default : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME
+TIMER = EXT_ETIME
+# For RS6K : SECOND and DSECND will use a call to the EXTERNAL FUNCTION ETIME_
+# TIMER = EXT_ETIME_
+# For gfortran compiler: SECOND and DSECND will use a call to the INTERNAL FUNCTION ETIME
+# TIMER = INT_ETIME
+# If your Fortran compiler does not provide etime (like Nag Fortran Compiler, etc...)
+# SECOND and DSECND will use a call to the INTERNAL FUNCTION CPU_TIME
+# TIMER = INT_CPU_TIME
+# If neither of this works...you can use the NONE value... In that case, SECOND and DSECND will always return 0
+# TIMER = NONE
+#
+# The archiver and the flag(s) to use when building archive (library)
+# If you system has no ranlib, set RANLIB = echo.
+#
+ARCH = ar
+ARCHFLAGS= cr
+RANLIB = echo
+#
+# The location of the libraries to which you will link. (The
+# machine-specific, optimized BLAS library should be used whenever
+# possible.)
+#
+XBLASLIB = libxblas.a
+BLASLIB = ../../blas$(PLAT).a
+#BLASLIB = -lessl
+LAPACKLIB = lapack$(PLAT).a
+TMGLIB = tmglib$(PLAT).a
+EIGSRCLIB = eigsrc$(PLAT).a
+LINSRCLIB = linsrc$(PLAT).a
diff --git a/INSTALL/org2.ps b/INSTALL/org2.ps
new file mode 100644
index 00000000..48159d69
--- /dev/null
+++ b/INSTALL/org2.ps
@@ -0,0 +1,768 @@
+%!PS-Adobe-3.0 EPSF-3.0
+%%Creator: xpdf/pdftops 3.00
+%%LanguageLevel: 2
+%%BoundingBox: 0 0 520 230
+%%DocumentSuppliedResources: (atend)
+%%EndComments
+%%BeginProlog
+%%BeginResource: procset xpdf 3.00 0
+/xpdf 75 dict def xpdf begin
+% PDF special state
+/pdfDictSize 15 def
+/pdfSetup {
+ 3 1 roll 2 array astore
+ /setpagedevice where {
+ pop 3 dict begin
+ /PageSize exch def
+ /ImagingBBox null def
+ /Policies 1 dict dup begin /PageSize 3 def end def
+ { /Duplex true def } if
+ currentdict end setpagedevice
+ } {
+ pop pop
+ } ifelse
+} def
+/pdfStartPage {
+ pdfDictSize dict begin
+ /pdfFill [0] def
+ /pdfStroke [0] def
+ /pdfLastFill false def
+ /pdfLastStroke false def
+ /pdfTextMat [1 0 0 1 0 0] def
+ /pdfFontSize 0 def
+ /pdfCharSpacing 0 def
+ /pdfTextRender 0 def
+ /pdfTextRise 0 def
+ /pdfWordSpacing 0 def
+ /pdfHorizScaling 1 def
+ /pdfTextClipPath [] def
+} def
+/pdfEndPage { end } def
+% separation convention operators
+/findcmykcustomcolor where {
+ pop
+}{
+ /findcmykcustomcolor { 5 array astore } def
+} ifelse
+/setcustomcolor where {
+ pop
+}{
+ /setcustomcolor {
+ exch
+ [ exch /Separation exch dup 4 get exch /DeviceCMYK exch
+ 0 4 getinterval cvx
+ [ exch /dup load exch { mul exch dup } /forall load
+ /pop load dup ] cvx
+ ] setcolorspace setcolor
+ } def
+} ifelse
+/customcolorimage where {
+ pop
+}{
+ /customcolorimage {
+ gsave
+ [ exch /Separation exch dup 4 get exch /DeviceCMYK exch
+ 0 4 getinterval
+ [ exch /dup load exch { mul exch dup } /forall load
+ /pop load dup ] cvx
+ ] setcolorspace
+ 10 dict begin
+ /ImageType 1 def
+ /DataSource exch def
+ /ImageMatrix exch def
+ /BitsPerComponent exch def
+ /Height exch def
+ /Width exch def
+ /Decode [1 0] def
+ currentdict end
+ image
+ grestore
+ } def
+} ifelse
+% PDF color state
+/sCol {
+ pdfLastStroke not {
+ pdfStroke aload length
+ dup 1 eq {
+ pop setgray
+ }{
+ dup 3 eq {
+ pop setrgbcolor
+ }{
+ 4 eq {
+ setcmykcolor
+ }{
+ findcmykcustomcolor exch setcustomcolor
+ } ifelse
+ } ifelse
+ } ifelse
+ /pdfLastStroke true def /pdfLastFill false def
+ } if
+} def
+/fCol {
+ pdfLastFill not {
+ pdfFill aload length
+ dup 1 eq {
+ pop setgray
+ }{
+ dup 3 eq {
+ pop setrgbcolor
+ }{
+ 4 eq {
+ setcmykcolor
+ }{
+ findcmykcustomcolor exch setcustomcolor
+ } ifelse
+ } ifelse
+ } ifelse
+ /pdfLastFill true def /pdfLastStroke false def
+ } if
+} def
+% build a font
+/pdfMakeFont {
+ 4 3 roll findfont
+ 4 2 roll matrix scale makefont
+ dup length dict begin
+ { 1 index /FID ne { def } { pop pop } ifelse } forall
+ /Encoding exch def
+ currentdict
+ end
+ definefont pop
+} def
+/pdfMakeFont16 {
+ exch findfont
+ dup length dict begin
+ { 1 index /FID ne { def } { pop pop } ifelse } forall
+ /WMode exch def
+ currentdict
+ end
+ definefont pop
+} def
+/pdfMakeFont16L3 {
+ 1 index /CIDFont resourcestatus {
+ pop pop 1 index /CIDFont findresource /CIDFontType known
+ } {
+ false
+ } ifelse
+ {
+ 0 eq { /Identity-H } { /Identity-V } ifelse
+ exch 1 array astore composefont pop
+ } {
+ pdfMakeFont16
+ } ifelse
+} def
+% graphics state operators
+/q { gsave pdfDictSize dict begin } def
+/Q { end grestore } def
+/cm { concat } def
+/d { setdash } def
+/i { setflat } def
+/j { setlinejoin } def
+/J { setlinecap } def
+/M { setmiterlimit } def
+/w { setlinewidth } def
+% color operators
+/g { dup 1 array astore /pdfFill exch def setgray
+ /pdfLastFill true def /pdfLastStroke false def } def
+/G { dup 1 array astore /pdfStroke exch def setgray
+ /pdfLastStroke true def /pdfLastFill false def } def
+/rg { 3 copy 3 array astore /pdfFill exch def setrgbcolor
+ /pdfLastFill true def /pdfLastStroke false def } def
+/RG { 3 copy 3 array astore /pdfStroke exch def setrgbcolor
+ /pdfLastStroke true def /pdfLastFill false def } def
+/k { 4 copy 4 array astore /pdfFill exch def setcmykcolor
+ /pdfLastFill true def /pdfLastStroke false def } def
+/K { 4 copy 4 array astore /pdfStroke exch def setcmykcolor
+ /pdfLastStroke true def /pdfLastFill false def } def
+/ck { 6 copy 6 array astore /pdfFill exch def
+ findcmykcustomcolor exch setcustomcolor
+ /pdfLastFill true def /pdfLastStroke false def } def
+/CK { 6 copy 6 array astore /pdfStroke exch def
+ findcmykcustomcolor exch setcustomcolor
+ /pdfLastStroke true def /pdfLastFill false def } def
+% path segment operators
+/m { moveto } def
+/l { lineto } def
+/c { curveto } def
+/re { 4 2 roll moveto 1 index 0 rlineto 0 exch rlineto
+ neg 0 rlineto closepath } def
+/h { closepath } def
+% path painting operators
+/S { sCol stroke } def
+/Sf { fCol stroke } def
+/f { fCol fill } def
+/f* { fCol eofill } def
+% clipping operators
+/W { clip newpath } def
+/W* { eoclip newpath } def
+% text state operators
+/Tc { /pdfCharSpacing exch def } def
+/Tf { dup /pdfFontSize exch def
+ dup pdfHorizScaling mul exch matrix scale
+ pdfTextMat matrix concatmatrix dup 4 0 put dup 5 0 put
+ exch findfont exch makefont setfont } def
+/Tr { /pdfTextRender exch def } def
+/Ts { /pdfTextRise exch def } def
+/Tw { /pdfWordSpacing exch def } def
+/Tz { /pdfHorizScaling exch def } def
+% text positioning operators
+/Td { pdfTextMat transform moveto } def
+/Tm { /pdfTextMat exch def } def
+% text string operators
+/cshow where {
+ pop
+ /cshow2 {
+ dup {
+ pop pop
+ 1 string dup 0 3 index put 3 index exec
+ } exch cshow
+ pop pop
+ } def
+}{
+ /cshow2 {
+ currentfont /FontType get 0 eq {
+ 0 2 2 index length 1 sub {
+ 2 copy get exch 1 add 2 index exch get
+ 2 copy exch 256 mul add
+ 2 string dup 0 6 5 roll put dup 1 5 4 roll put
+ 3 index exec
+ } for
+ } {
+ dup {
+ 1 string dup 0 3 index put 3 index exec
+ } forall
+ } ifelse
+ pop pop
+ } def
+} ifelse
+/awcp {
+ exch {
+ false charpath
+ 5 index 5 index rmoveto
+ 6 index eq { 7 index 7 index rmoveto } if
+ } exch cshow2
+ 6 {pop} repeat
+} def
+/Tj {
+ fCol
+ 1 index stringwidth pdfTextMat idtransform pop
+ sub 1 index length dup 0 ne { div } { pop pop 0 } ifelse
+ pdfWordSpacing pdfHorizScaling mul 0 pdfTextMat dtransform 32
+ 4 3 roll pdfCharSpacing pdfHorizScaling mul add 0
+ pdfTextMat dtransform
+ 6 5 roll Tj1
+} def
+/Tj16 {
+ fCol
+ 2 index stringwidth pdfTextMat idtransform pop
+ sub exch div
+ pdfWordSpacing pdfHorizScaling mul 0 pdfTextMat dtransform 32
+ 4 3 roll pdfCharSpacing pdfHorizScaling mul add 0
+ pdfTextMat dtransform
+ 6 5 roll Tj1
+} def
+/Tj16V {
+ fCol
+ 2 index stringwidth pdfTextMat idtransform exch pop
+ sub exch div
+ 0 pdfWordSpacing pdfTextMat dtransform 32
+ 4 3 roll pdfCharSpacing add 0 exch
+ pdfTextMat dtransform
+ 6 5 roll Tj1
+} def
+/Tj1 {
+ 0 pdfTextRise pdfTextMat dtransform rmoveto
+ currentpoint 8 2 roll
+ pdfTextRender 1 and 0 eq {
+ 6 copy awidthshow
+ } if
+ pdfTextRender 3 and dup 1 eq exch 2 eq or {
+ 7 index 7 index moveto
+ 6 copy
+ currentfont /FontType get 3 eq { fCol } { sCol } ifelse
+ false awcp currentpoint stroke moveto
+ } if
+ pdfTextRender 4 and 0 ne {
+ 8 6 roll moveto
+ false awcp
+ /pdfTextClipPath [ pdfTextClipPath aload pop
+ {/moveto cvx}
+ {/lineto cvx}
+ {/curveto cvx}
+ {/closepath cvx}
+ pathforall ] def
+ currentpoint newpath moveto
+ } {
+ 8 {pop} repeat
+ } ifelse
+ 0 pdfTextRise neg pdfTextMat dtransform rmoveto
+} def
+/TJm { pdfFontSize 0.001 mul mul neg 0
+ pdfTextMat dtransform rmoveto } def
+/TJmV { pdfFontSize 0.001 mul mul neg 0 exch
+ pdfTextMat dtransform rmoveto } def
+/Tclip { pdfTextClipPath cvx exec clip newpath
+ /pdfTextClipPath [] def } def
+% Level 2 image operators
+/pdfImBuf 100 string def
+/pdfIm {
+ image
+ { currentfile pdfImBuf readline
+ not { pop exit } if
+ (%-EOD-) eq { exit } if } loop
+} def
+/pdfImSep {
+ findcmykcustomcolor exch
+ dup /Width get /pdfImBuf1 exch string def
+ dup /Decode get aload pop 1 index sub /pdfImDecodeRange exch def
+ /pdfImDecodeLow exch def
+ begin Width Height BitsPerComponent ImageMatrix DataSource end
+ /pdfImData exch def
+ { pdfImData pdfImBuf1 readstring pop
+ 0 1 2 index length 1 sub {
+ 1 index exch 2 copy get
+ pdfImDecodeRange mul 255 div pdfImDecodeLow add round cvi
+ 255 exch sub put
+ } for }
+ 6 5 roll customcolorimage
+ { currentfile pdfImBuf readline
+ not { pop exit } if
+ (%-EOD-) eq { exit } if } loop
+} def
+/pdfImM {
+ fCol imagemask
+ { currentfile pdfImBuf readline
+ not { pop exit } if
+ (%-EOD-) eq { exit } if } loop
+} def
+end
+%%EndResource
+%%EndProlog
+%%BeginSetup
+xpdf begin
+%%BeginResource: font T3_9_0
+8 dict begin
+/FontType 3 def
+/FontMatrix [0.001 0 0 0.001 0 0] def
+/FontBBox [-50 -250 1000 1000] def
+/Encoding 256 array def
+ 0 1 255 { Encoding exch /.notdef put } for
+/BuildGlyph {
+ exch /CharProcs get exch
+ 2 copy known not { pop /.notdef } if
+ get exec
+} bind def
+/BuildChar {
+ 1 index /Encoding get exch get
+ 1 index /BuildGlyph get exec
+} bind def
+/CharProcs 1 dict def
+CharProcs begin
+/Cbr {
+0 0 -50 -250 0 1000 setcachedevice
+q
+q
+-50 -250 50 1250 re
+W
+[] 0 d
+40 w
+10 M
+0 J
+0 j
+0 -250 m
+0 750 l
+Sf
+Q
+Q
+} def
+end
+currentdict end
+/T3_9_0 exch definefont pop
+%%EndResource
+/F9_0 /T3_9_0 1 1
+[ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /space/exclam/quotedbl/numbersign/dollar/percent/ampersand/quoteright
+ /parenleft/parenright/asterisk/plus/comma/hyphen/period/slash
+ /zero/one/two/three/four/five/six/seven
+ /eight/nine/colon/semicolon/less/equal/greater/question
+ /at/A/B/C/D/E/F/G
+ /H/I/J/K/Cbr/M/N/O
+ /P/Q/R/S/T/U/V/W
+ /X/Y/Z/bracketleft/backslash/bracketright/asciicircum/underscore
+ /quoteleft/a/b/c/d/e/f/g
+ /h/i/j/k/l/m/n/o
+ /p/q/r/s/t/u/v/w
+ /x/y/z/braceleft/bar/braceright/asciitilde/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/exclamdown/cent/sterling/fraction/yen/florin/section
+ /currency/quotesingle/quotedblleft/guillemotleft/guilsinglleft/guilsinglright/fi/fl
+ /.notdef/endash/dagger/daggerdbl/periodcentered/.notdef/paragraph/bullet
+ /quotesinglbase/quotedblbase/quotedblright/guillemotright/ellipsis/perthousand/.notdef/questiondown
+ /.notdef/grave/acute/circumflex/tilde/macron/breve/dotaccent
+ /dieresis/.notdef/ring/cedilla/.notdef/hungarumlaut/ogonek/caron
+ /emdash/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/AE/.notdef/ordfeminine/.notdef/.notdef/.notdef/.notdef
+ /Lslash/Oslash/OE/ordmasculine/.notdef/.notdef/.notdef/.notdef
+ /.notdef/ae/.notdef/.notdef/.notdef/dotlessi/.notdef/.notdef
+ /lslash/oslash/oe/germandbls/.notdef/.notdef/.notdef/.notdef]
+pdfMakeFont
+/F8_0 /Times-Roman 1 1
+[ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /space/exclam/quotedbl/numbersign/dollar/percent/ampersand/quoteright
+ /parenleft/parenright/asterisk/plus/comma/hyphen/period/slash
+ /zero/one/two/three/four/five/six/seven
+ /eight/nine/colon/semicolon/less/equal/greater/question
+ /at/A/B/C/D/E/F/G
+ /H/I/J/K/L/M/N/O
+ /P/Q/R/S/T/U/V/W
+ /X/Y/Z/bracketleft/backslash/bracketright/asciicircum/underscore
+ /quoteleft/a/b/c/d/e/f/g
+ /h/i/j/k/l/m/n/o
+ /p/q/r/s/t/u/v/w
+ /x/y/z/braceleft/bar/braceright/asciitilde/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/exclamdown/cent/sterling/fraction/yen/florin/section
+ /currency/quotesingle/quotedblleft/guillemotleft/guilsinglleft/guilsinglright/fi/fl
+ /.notdef/endash/dagger/daggerdbl/periodcentered/.notdef/paragraph/bullet
+ /quotesinglbase/quotedblbase/quotedblright/guillemotright/ellipsis/perthousand/.notdef/questiondown
+ /.notdef/grave/acute/circumflex/tilde/macron/breve/dotaccent
+ /dieresis/.notdef/ring/cedilla/.notdef/hungarumlaut/ogonek/caron
+ /emdash/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef/.notdef
+ /.notdef/AE/.notdef/ordfeminine/.notdef/.notdef/.notdef/.notdef
+ /Lslash/Oslash/OE/ordmasculine/.notdef/.notdef/.notdef/.notdef
+ /.notdef/ae/.notdef/.notdef/.notdef/dotlessi/.notdef/.notdef
+ /lslash/oslash/oe/germandbls/.notdef/.notdef/.notdef/.notdef]
+pdfMakeFont
+%%EndSetup
+pdfStartPage
+[] 0 d
+1 i
+0 j
+0 J
+10 M
+1 w
+0 g
+0 G
+q
+q
+[0.1 0 0 0.1 0 0] cm
+0 G
+0 g
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 216.4 212.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(LAP) 20.779 Tj
+34.4549 TJm
+(ACK) 23.221 Tj
+Q
+2.4 w
+1 i
+2382 2078 m
+315.598 1538 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 5.69961 140.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(INST) 24.442 Tj
+85.601 TJm
+(ALL) 21.384 Tj
+Q
+280 1358 m
+280 1178 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 -1.5 108.9] Tm
+0 0 Td
+/F8_0 9 Tf
+(Machine) 31.491 Tj
+-289.845 TJm
+(depen-) 24.489 Tj
+5.69961 -10.8 Td
+(dent) 15.498 Tj
+-278.043 TJm
+(routines) 28.998 Tj
+Q
+2382 2078 m
+1143.6 1538 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 96.9 140.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(BLAS) 28.116 Tj
+Q
+1108 1358 m
+748.004 818.004 l
+S
+1108 1358 m
+1468 818.004 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 64.4996 68.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(SRC) 20.79 Tj
+10.3004 -13.4 Td
+/F9_0 11 Tf
+(L) 0 Tj
+10.3004 -24 Td
+(L) 0 Tj
+-16.0996 -35.5004 Td
+/F8_0 9 Tf
+(Level) 20.493 Tj
+-278.512 TJm
+(1) 4.5 Tj
+-255.556 TJm
+(BLAS) 23.004 Tj
+-16.0996 -46.3004 Td
+(Level) 20.493 Tj
+-278.512 TJm
+(2) 4.5 Tj
+-255.556 TJm
+(BLAS) 23.004 Tj
+-16.0996 -57.1004 Td
+(Level) 20.493 Tj
+-278.512 TJm
+(3) 4.5 Tj
+-255.556 TJm
+(BLAS) 23.004 Tj
+59.5004 7.10543e-15 Td
+/F8_0 11 Tf
+(TESTING) 45.826 Tj
+82.3004 -13.4 Td
+/F9_0 11 Tf
+(L) 0 Tj
+82.3004 -24 Td
+(L) 0 Tj
+53.3004 -35.5004 Td
+/F8_0 9 Tf
+(BLAS2) 27.504 Tj
+-244 TJm
+(&) 7.002 Tj
+-233.111 TJm
+(3) 4.5 Tj
+-255.556 TJm
+(test) 12.501 Tj
+67.7004 -46.3004 Td
+(routines) 28.998 Tj
+Q
+2382 2078 m
+1935.6 1538 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 183.3 140.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(SRC) 20.79 Tj
+Q
+1936 1358 m
+1936 1178 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 160 108.9] Tm
+0 0 Td
+/F8_0 9 Tf
+(LAP) 17.001 Tj
+22.3334 TJm
+(ACK) 18.999 Tj
+-233.445 TJm
+(routines) 28.998 Tj
+-3.10039 -10.8 Td
+(&) 7.002 Tj
+-233.154 TJm
+(auxiliary) 31.995 Tj
+-333.845 TJm
+(routines) 28.998 Tj
+Q
+2382 2078 m
+2907.59 1538 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 268 140.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(TESTING) 45.826 Tj
+Q
+2908 1358 m
+2296 818.004 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 290.8 127.4] Tm
+0 0 Td
+/F9_0 11 Tf
+(L) 0 Tj
+0 -9.80039 Td
+(L) 0 Tj
+0 -20.9004 Td
+(L) 0 Tj
+0 -31.9004 Td
+(L) 0 Tj
+0 -43.0004 Td
+(L) 0 Tj
+Q
+2908 1358 m
+3520 818.004 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 216.9 68.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(LIN) 18.326 Tj
+9.10039 -13.4 Td
+/F9_0 11 Tf
+(L) 0 Tj
+9.10039 -24 Td
+(L) 0 Tj
+50.9004 0 Td
+/F8_0 11 Tf
+(MA) 17.721 Tj
+83.7269 TJm
+(TGEN) 29.326 Tj
+73.9004 -13.4 Td
+/F9_0 11 Tf
+(L) 0 Tj
+73.9004 -24 Td
+(L) 0 Tj
+129.6 0 Td
+/F8_0 11 Tf
+(EIG) 18.326 Tj
+138.7 -13.4 Td
+/F9_0 11 Tf
+(L) 0 Tj
+138.7 -24 Td
+(L) 0 Tj
+-11.4996 -35.5004 Td
+/F8_0 9 Tf
+(Linear) 23.49 Tj
+-290.001 TJm
+(eqn.) 15.246 Tj
+-12.9996 -46.3004 Td
+(test) 12.501 Tj
+-266.555 TJm
+(routines) 28.998 Tj
+53.3004 -35.5004 Td
+(T) 5.499 Tj
+55.4443 TJm
+(est) 9.999 Tj
+-244.512 TJm
+(matrix) 23.499 Tj
+54.9 -46.3004 Td
+(generators) 37.485 Tj
+115.7 -35.5004 Td
+(Eigensystem) 45.999 Tj
+116.6 -46.3004 Td
+(test) 12.501 Tj
+-266.599 TJm
+(routines) 28.998 Tj
+Q
+2382 2078 m
+4527.59 1538 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 436.7 140.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(TIMING) 39.71 Tj
+Q
+4564 1358 m
+4204 818.004 l
+S
+4564 1358 m
+4924 818.004 l
+S
+q
+[10 0 0 10 0 0] cm
+[1 0 0 1 0 0] Tm
+0 0 Td
+[1 0 0 1 411.3 68.8] Tm
+0 0 Td
+/F8_0 11 Tf
+(LIN) 18.326 Tj
+9.1 -13.4 Td
+/F9_0 11 Tf
+(L) 0 Tj
+9.1 -24 Td
+(L) 0 Tj
+72 0 Td
+/F8_0 11 Tf
+(EIG) 18.326 Tj
+81.1 -13.4 Td
+/F9_0 11 Tf
+(L) 0 Tj
+81.1 -24 Td
+(L) 0 Tj
+-11.5004 -35.5004 Td
+/F8_0 9 Tf
+(Linear) 23.49 Tj
+-290.001 TJm
+(eqn.) 15.246 Tj
+-18.7004 -46.3004 Td
+(timing) 23.508 Tj
+-288 TJm
+(routines) 28.998 Tj
+58.0996 -35.5004 Td
+(Eigensystem) 45.999 Tj
+53.2996 -46.3004 Td
+(timing) 23.508 Tj
+-288 TJm
+(routines) 28.998 Tj
+Q
+Q
+Q
+showpage
+%%PageTrailer
+pdfEndPage
+%%Trailer
+end
+%%DocumentSuppliedResources:
+%%+ font T3_9_0
+%%EOF
diff --git a/INSTALL/psfig.tex b/INSTALL/psfig.tex
new file mode 100644
index 00000000..e1e65a92
--- /dev/null
+++ b/INSTALL/psfig.tex
@@ -0,0 +1,391 @@
+% Psfig/TeX Release 1.2
+% dvi2ps-li version
+%
+% All software, documentation, and related files in this distribution of
+% psfig/tex are Copyright 1987, 1988 Trevor J. Darrell
+%
+% Permission is granted for use and non-profit distribution of psfig/tex
+% providing that this notice be clearly maintained, but the right to
+% distribute any portion of psfig/tex for profit or as part of any commercial
+% product is specifically reserved for the author.
+%
+% $Header$
+% $Source$
+%
+% Thanks to Greg Hager (GDH) and Ned Batchelder for their contributions
+% to this project.
+%
+\catcode`\@=11\relax
+\newwrite\@unused
+\def\typeout#1{{\let\protect\string\immediate\write\@unused{#1}}}
+\typeout{psfig/tex 1.2-dvi2ps-li}
+
+%% Here's how you define your figure path. Should be set up with null
+%% default and a user useable definition.
+
+\def\figurepath{./}
+\def\psfigurepath#1{\edef\figurepath{#1}}
+
+%
+% @psdo control structure -- similar to Latex @for.
+% I redefined these with different names so that psfig can
+% be used with TeX as well as LaTeX, and so that it will not
+% be vunerable to future changes in LaTeX's internal
+% control structure,
+%
+\def\@nnil{\@nil}
+\def\@empty{}
+\def\@psdonoop#1\@@#2#3{}
+\def\@psdo#1:=#2\do#3{\edef\@psdotmp{#2}\ifx\@psdotmp\@empty \else
+ \expandafter\@psdoloop#2,\@nil,\@nil\@@#1{#3}\fi}
+\def\@psdoloop#1,#2,#3\@@#4#5{\def#4{#1}\ifx #4\@nnil \else
+ #5\def#4{#2}\ifx #4\@nnil \else#5\@ipsdoloop #3\@@#4{#5}\fi\fi}
+\def\@ipsdoloop#1,#2\@@#3#4{\def#3{#1}\ifx #3\@nnil
+ \let\@nextwhile=\@psdonoop \else
+ #4\relax\let\@nextwhile=\@ipsdoloop\fi\@nextwhile#2\@@#3{#4}}
+\def\@tpsdo#1:=#2\do#3{\xdef\@psdotmp{#2}\ifx\@psdotmp\@empty \else
+ \@tpsdoloop#2\@nil\@nil\@@#1{#3}\fi}
+\def\@tpsdoloop#1#2\@@#3#4{\def#3{#1}\ifx #3\@nnil
+ \let\@nextwhile=\@psdonoop \else
+ #4\relax\let\@nextwhile=\@tpsdoloop\fi\@nextwhile#2\@@#3{#4}}
+%
+%
+\def\psdraft{
+ \def\@psdraft{0}
+ %\typeout{draft level now is \@psdraft \space . }
+}
+\def\psfull{
+ \def\@psdraft{100}
+ %\typeout{draft level now is \@psdraft \space . }
+}
+\psfull
+\newif\if@prologfile
+\newif\if@postlogfile
+\newif\if@noisy
+\def\pssilent{
+ \@noisyfalse
+}
+\def\psnoisy{
+ \@noisytrue
+}
+\psnoisy
+%%% These are for the option list.
+%%% A specification of the form a = b maps to calling \@p@@sa{b}
+\newif\if@bbllx
+\newif\if@bblly
+\newif\if@bburx
+\newif\if@bbury
+\newif\if@height
+\newif\if@width
+\newif\if@rheight
+\newif\if@rwidth
+\newif\if@clip
+\newif\if@verbose
+\def\@p@@sclip#1{\@cliptrue}
+
+%%% GDH 7/26/87 -- changed so that it first looks in the local directory,
+%%% then in a specified global directory for the ps file.
+
+\def\@p@@sfile#1{\def\@p@sfile{null}%
+ \openin1=#1
+ \ifeof1\closein1%
+ \openin1=\figurepath#1
+ \ifeof1\typeout{Error, File #1 not found}
+ \else\closein1
+ \edef\@p@sfile{\figurepath#1}%
+ \fi%
+ \else\closein1%
+ \def\@p@sfile{#1}%
+ \fi}
+\def\@p@@sfigure#1{\def\@p@sfile{null}%
+ \openin1=#1
+ \ifeof1\closein1%
+ \openin1=\figurepath#1
+ \ifeof1\typeout{Error, File #1 not found}
+ \else\closein1
+ \def\@p@sfile{\figurepath#1}%
+ \fi%
+ \else\closein1%
+ \def\@p@sfile{#1}%
+ \fi}
+
+\def\@p@@sbbllx#1{
+ %\typeout{bbllx is #1}
+ \@bbllxtrue
+ \dimen100=#1
+ \edef\@p@sbbllx{\number\dimen100}
+}
+\def\@p@@sbblly#1{
+ %\typeout{bblly is #1}
+ \@bbllytrue
+ \dimen100=#1
+ \edef\@p@sbblly{\number\dimen100}
+}
+\def\@p@@sbburx#1{
+ %\typeout{bburx is #1}
+ \@bburxtrue
+ \dimen100=#1
+ \edef\@p@sbburx{\number\dimen100}
+}
+\def\@p@@sbbury#1{
+ %\typeout{bbury is #1}
+ \@bburytrue
+ \dimen100=#1
+ \edef\@p@sbbury{\number\dimen100}
+}
+\def\@p@@sheight#1{
+ \@heighttrue
+ \dimen100=#1
+ \edef\@p@sheight{\number\dimen100}
+ %\typeout{Height is \@p@sheight}
+}
+\def\@p@@swidth#1{
+ %\typeout{Width is #1}
+ \@widthtrue
+ \dimen100=#1
+ \edef\@p@swidth{\number\dimen100}
+}
+\def\@p@@srheight#1{
+ %\typeout{Reserved height is #1}
+ \@rheighttrue
+ \dimen100=#1
+ \edef\@p@srheight{\number\dimen100}
+}
+\def\@p@@srwidth#1{
+ %\typeout{Reserved width is #1}
+ \@rwidthtrue
+ \dimen100=#1
+ \edef\@p@srwidth{\number\dimen100}
+}
+\def\@p@@ssilent#1{
+ \@verbosefalse
+}
+\def\@p@@sprolog#1{\@prologfiletrue\def\@prologfileval{#1}}
+\def\@p@@spostlog#1{\@postlogfiletrue\def\@postlogfileval{#1}}
+\def\@cs@name#1{\csname #1\endcsname}
+\def\@setparms#1=#2,{\@cs@name{@p@@s#1}{#2}}
+%
+% initialize the defaults (size the size of the figure)
+%
+\def\ps@init@parms{
+ \@bbllxfalse \@bbllyfalse
+ \@bburxfalse \@bburyfalse
+ \@heightfalse \@widthfalse
+ \@rheightfalse \@rwidthfalse
+ \def\@p@sbbllx{}\def\@p@sbblly{}
+ \def\@p@sbburx{}\def\@p@sbbury{}
+ \def\@p@sheight{}\def\@p@swidth{}
+ \def\@p@srheight{}\def\@p@srwidth{}
+ \def\@p@sfile{}
+ \def\@p@scost{10}
+ \def\@sc{}
+ \@prologfilefalse
+ \@postlogfilefalse
+ \@clipfalse
+ \if@noisy
+ \@verbosetrue
+ \else
+ \@verbosefalse
+ \fi
+
+}
+%
+% Go through the options setting things up.
+%
+\def\parse@ps@parms#1{
+ \@psdo\@psfiga:=#1\do
+ {\expandafter\@setparms\@psfiga,}}
+%
+% Compute bb height and width
+%
+\newif\ifno@bb
+\newif\ifnot@eof
+\newread\ps@stream
+\def\bb@missing{
+ \if@verbose{
+ \typeout{psfig: searching \@p@sfile \space for bounding box}
+ }\fi
+ \openin\ps@stream=\@p@sfile
+ \no@bbtrue
+ \not@eoftrue
+ \catcode`\%=12
+ \loop
+ \read\ps@stream to \line@in
+ \global\toks200=\expandafter{\line@in}
+ \ifeof\ps@stream \not@eoffalse \fi
+ %\typeout{ looking at :: \the\toks200 }
+ \@bbtest{\toks200}
+ \if@bbmatch\not@eoffalse\expandafter\bb@cull\the\toks200\fi
+ \ifnot@eof \repeat
+ \catcode`\%=14
+}
+\catcode`\%=12
+\newif\if@bbmatch
+\def\@bbtest#1{\expandafter\@a@\the#1%%BoundingBox:\@bbtest\@a@}
+\long\def\@a@#1%%BoundingBox:#2#3\@a@{\ifx\@bbtest#2\@bbmatchfalse\else\@bbmatchtrue\fi}
+\long\def\bb@cull#1 #2 #3 #4 #5 {
+ \dimen100=#2 bp\edef\@p@sbbllx{\number\dimen100}
+ \dimen100=#3 bp\edef\@p@sbblly{\number\dimen100}
+ \dimen100=#4 bp\edef\@p@sbburx{\number\dimen100}
+ \dimen100=#5 bp\edef\@p@sbbury{\number\dimen100}
+ \no@bbfalse
+}
+\catcode`\%=14
+%
+\def\compute@bb{
+ \no@bbfalse
+ \if@bbllx \else \no@bbtrue \fi
+ \if@bblly \else \no@bbtrue \fi
+ \if@bburx \else \no@bbtrue \fi
+ \if@bbury \else \no@bbtrue \fi
+ \ifno@bb \bb@missing \fi
+ \ifno@bb \typeout{FATAL ERROR: no bb supplied or found}
+ \no-bb-error
+ \fi
+ %
+ \count203=\@p@sbburx
+ \count204=\@p@sbbury
+ \advance\count203 by -\@p@sbbllx
+ \advance\count204 by -\@p@sbblly
+ \edef\@bbw{\number\count203}
+ \edef\@bbh{\number\count204}
+ %\typeout{ bbh = \@bbh, bbw = \@bbw }
+}
+%
+% \in@hundreds performs #1 * (#2 / #3) correct to the hundreds,
+% then leaves the result in @result
+%
+\def\in@hundreds#1#2#3{\count240=#2 \count241=#3
+ \count100=\count240 % 100 is first digit #2/#3
+ \divide\count100 by \count241
+ \count101=\count100
+ \multiply\count101 by \count241
+ \advance\count240 by -\count101
+ \multiply\count240 by 10
+ \count101=\count240 %101 is second digit of #2/#3
+ \divide\count101 by \count241
+ \count102=\count101
+ \multiply\count102 by \count241
+ \advance\count240 by -\count102
+ \multiply\count240 by 10
+ \count102=\count240 % 102 is the third digit
+ \divide\count102 by \count241
+ \count200=#1\count205=0
+ \count201=\count200
+ \multiply\count201 by \count100
+ \advance\count205 by \count201
+ \count201=\count200
+ \divide\count201 by 10
+ \multiply\count201 by \count101
+ \advance\count205 by \count201
+ %
+ \count201=\count200
+ \divide\count201 by 100
+ \multiply\count201 by \count102
+ \advance\count205 by \count201
+ %
+ \edef\@result{\number\count205}
+}
+\def\compute@wfromh{
+ % computing : width = height * (bbw / bbh)
+ \in@hundreds{\@p@sheight}{\@bbw}{\@bbh}
+ %\typeout{ \@p@sheight * \@bbw / \@bbh, = \@result }
+ \edef\@p@swidth{\@result}
+ %\typeout{w from h: width is \@p@swidth}
+}
+\def\compute@hfromw{
+ % computing : height = width * (bbh / bbw)
+ \in@hundreds{\@p@swidth}{\@bbh}{\@bbw}
+ %\typeout{ \@p@swidth * \@bbh / \@bbw = \@result }
+ \edef\@p@sheight{\@result}
+ %\typeout{h from w : height is \@p@sheight}
+}
+\def\compute@handw{
+ \if@height
+ \if@width
+ \else
+ \compute@wfromh
+ \fi
+ \else
+ \if@width
+ \compute@hfromw
+ \else
+ \edef\@p@sheight{\@bbh}
+ \edef\@p@swidth{\@bbw}
+ \fi
+ \fi
+}
+\def\compute@resv{
+ \if@rheight \else \edef\@p@srheight{\@p@sheight} \fi
+ \if@rwidth \else \edef\@p@srwidth{\@p@swidth} \fi
+}
+%
+% Compute any missing values
+\def\compute@sizes{
+ \compute@bb
+ \compute@handw
+ \compute@resv
+}
+%
+% \psfig
+% usage : \psfig{file=, height=, width=, bbllx=, bblly=, bburx=, bbury=,
+% rheight=, rwidth=, clip=}
+%
+% "clip=" is a switch and takes no value, but the `=' must be present.
+\def\psfig#1{\vbox {
+ % do a zero width hard space so that a single
+ % \psfig in a centering enviornment will behave nicely
+ %{\setbox0=\hbox{\ }\ \hskip-\wd0}
+ %
+ \ps@init@parms
+ \parse@ps@parms{#1}
+ \compute@sizes
+ %
+ \ifnum\@p@scost<\@psdraft{
+ \if@verbose{
+ \typeout{psfig: including \@p@sfile \space }
+ }\fi
+ %
+ \special{ pstext="\@p@swidth \space
+ \@p@sheight \space
+ \@p@sbbllx \space \@p@sbblly \space
+ \@p@sbburx \space
+ \@p@sbbury \space startTexFig" \space}
+ \if@clip{
+ \if@verbose{
+ \typeout{(clip)}
+ }\fi
+ \special{ pstext="doclip \space"}
+ }\fi
+ \if@prologfile
+ \special{psfile=\@prologfileval \space } \fi
+ \special{psfile=\@p@sfile \space }
+ \if@postlogfile
+ \special{psfile=\@postlogfileval \space } \fi
+ \special{pstext=endTexFig \space }
+ % Create the vbox to reserve the space for the figure
+ \vbox to \@p@srheight true sp{
+ \hbox to \@p@srwidth true sp{
+ \hss
+ }
+ \vss
+ }
+ }\else{
+ % draft figure, just reserve the space and print the
+ % path name.
+ \vbox to \@p@srheight true sp{
+ \vss
+ \hbox to \@p@srwidth true sp{
+ \hss
+ \if@verbose{
+ \@p@sfile
+ }\fi
+ \hss
+ }
+ \vss
+ }
+ }\fi
+}}
+\def\psglobal{\typeout{psfig: PSGLOBAL is OBSOLETE; use psprint -m instead}}
+\catcode`\@=12\relax
+
diff --git a/INSTALL/second_EXT_ETIME.f b/INSTALL/second_EXT_ETIME.f
new file mode 100644
index 00000000..e94b578b
--- /dev/null
+++ b/INSTALL/second_EXT_ETIME.f
@@ -0,0 +1,33 @@
+ REAL FUNCTION SECOND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* SECOND returns the user time for a process in seconds.
+* This version gets the time from the EXTERNAL system function ETIME.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ REAL T1
+* ..
+* .. Local Arrays ..
+ REAL TARRAY( 2 )
+* ..
+* .. External Functions ..
+ REAL ETIME
+ EXTERNAL ETIME
+* ..
+* .. Executable Statements ..
+*
+ T1 = ETIME( TARRAY )
+ SECOND = TARRAY( 1 )
+ RETURN
+*
+* End of SECOND
+*
+ END
diff --git a/INSTALL/second_EXT_ETIME_.f b/INSTALL/second_EXT_ETIME_.f
new file mode 100644
index 00000000..63455276
--- /dev/null
+++ b/INSTALL/second_EXT_ETIME_.f
@@ -0,0 +1,33 @@
+ REAL FUNCTION SECOND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* SECOND returns the user time for a process in seconds.
+* This version gets the time from the system function ETIME_.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ REAL T1
+* ..
+* .. Local Arrays ..
+ REAL TARRAY( 2 )
+* ..
+* .. External Functions ..
+ REAL ETIME_
+ EXTERNAL ETIME_
+* ..
+* .. Executable Statements ..
+*
+ T1 = ETIME_( TARRAY )
+ SECOND = TARRAY( 1 )
+ RETURN
+*
+* End of SECOND
+*
+ END
diff --git a/INSTALL/second_INT_CPU_TIME.f b/INSTALL/second_INT_CPU_TIME.f
new file mode 100644
index 00000000..40fee9b0
--- /dev/null
+++ b/INSTALL/second_INT_CPU_TIME.f
@@ -0,0 +1,31 @@
+ REAL FUNCTION SECOND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* SECOND returns the user time for a process in seconds.
+* This version gets the time from the INTERNAL function CPU_TIME.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+*
+ REAL T
+*
+* .. Intrinsic Functions ..
+*
+ INTRINSIC CPU_TIME
+*
+* .. Executable Statements .. *
+*
+ CALL CPU_TIME( T )
+ SECOND = T
+ RETURN
+*
+* End of SECOND
+*
+ END
diff --git a/INSTALL/second_INT_ETIME.f b/INSTALL/second_INT_ETIME.f
new file mode 100644
index 00000000..10aa1563
--- /dev/null
+++ b/INSTALL/second_INT_ETIME.f
@@ -0,0 +1,33 @@
+ REAL FUNCTION SECOND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* SECOND returns the user time for a process in seconds.
+* This version gets the time from the INTERNAL function ETIME.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ REAL T1
+* ..
+* .. Local Arrays ..
+ REAL TARRAY( 2 )
+* ..
+* .. Intrinsic Functions ..
+ REAL ETIME
+ INTRINSIC ETIME
+* ..
+* .. Executable Statements ..
+*
+ T1 = ETIME( TARRAY )
+ SECOND = TARRAY( 1 )
+ RETURN
+*
+* End of SECOND
+*
+ END
diff --git a/INSTALL/second_NONE.f b/INSTALL/second_NONE.f
new file mode 100644
index 00000000..ff0ef673
--- /dev/null
+++ b/INSTALL/second_NONE.f
@@ -0,0 +1,22 @@
+ REAL FUNCTION SECOND( )
+*
+* -- LAPACK auxiliary routine (version 3.1.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* February 2007
+*
+* Purpose
+* =======
+*
+* SECOND returns nothing instead of returning the user time for a process in seconds.
+* If you are using that routine, it means that neither EXTERNAL ETIME,
+* EXTERNAL ETIME_, INTERNAL ETIME, INTERNAL CPU_TIME is available on
+* your machine.
+*
+* =====================================================================
+*
+ SECOND = 0.0E+0
+ RETURN
+*
+* End of SECOND
+*
+ END
diff --git a/INSTALL/secondtst.f b/INSTALL/secondtst.f
new file mode 100644
index 00000000..dffd13ba
--- /dev/null
+++ b/INSTALL/secondtst.f
@@ -0,0 +1,91 @@
+ PROGRAM TEST4
+*
+* -- LAPACK test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Parameters ..
+ INTEGER NMAX, ITS
+ PARAMETER ( NMAX = 100, ITS = 5000 )
+* ..
+* .. Local Scalars ..
+ INTEGER I, J
+ REAL ALPHA, AVG, T1, T2, TNOSEC
+* ..
+* .. Local Arrays ..
+ REAL X( NMAX ), Y( NMAX )
+* ..
+* .. External Functions ..
+ REAL SECOND
+ EXTERNAL SECOND
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC REAL
+* ..
+* .. Executable Statements ..
+*
+*
+* Initialize X and Y
+*
+ DO 10 I = 1, NMAX
+ X( I ) = REAL( 1 ) / REAL( I )
+ Y( I ) = REAL( NMAX-I ) / REAL( NMAX )
+ 10 CONTINUE
+ ALPHA = 0.315
+*
+* Time 1,000,000 SAXPY operations
+*
+ T1 = SECOND( )
+ DO 30 J = 1, ITS
+ DO 20 I = 1, NMAX
+ Y( I ) = Y( I ) + ALPHA*X( I )
+ 20 CONTINUE
+ ALPHA = -ALPHA
+ 30 CONTINUE
+ T2 = SECOND( )
+ WRITE( 6, 9999 )T2 - T1
+ IF( T2-T1.GT.0.0 ) THEN
+ WRITE( 6, 9998 )1.0 / ( T2-T1 )
+ ELSE
+ WRITE( 6, 9994 )
+ END IF
+ TNOSEC = T2 - T1
+*
+* Time 1,000,000 SAXPY operations with SECOND in the outer loop
+*
+ T1 = SECOND( )
+ DO 50 J = 1, ITS
+ DO 40 I = 1, NMAX
+ Y( I ) = Y( I ) + ALPHA*X( I )
+ 40 CONTINUE
+ ALPHA = -ALPHA
+ T2 = SECOND( )
+ 50 CONTINUE
+*
+* Compute the time used in milliseconds used by an average call
+* to SECOND.
+*
+ WRITE( 6, 9997 )T2 - T1
+ AVG = ( ( T2-T1 ) - TNOSEC ) * 1000./REAL( ITS )
+ WRITE( 6, 9996 )AVG
+*
+* Compute the equivalent number of floating point operations used
+* by an average call to SECOND.
+*
+ IF( TNOSEC.GT.0.0 )
+ $ WRITE( 6, 9995 )1000.*AVG / TNOSEC
+*
+ 9999 FORMAT( ' Time for 1,000,000 SAXPY ops = ', G10.3, ' seconds' )
+ 9998 FORMAT( ' SAXPY performance rate = ', G10.3, ' mflops ' )
+ 9997 FORMAT( ' Including SECOND, time = ', G10.3, ' seconds' )
+ 9996 FORMAT( ' Average time for SECOND = ', G10.3,
+ $ ' milliseconds' )
+ 9995 FORMAT( ' Equivalent floating point ops = ', G10.3, ' ops' )
+ 9994 FORMAT( ' *** Error: Time for operations was zero' )
+ CALL MYSUB(NMAX,X,Y)
+ END
+ SUBROUTINE MYSUB(N,X,Y)
+ INTEGER N
+ REAL X(N), Y(N)
+ RETURN
+ END
diff --git a/INSTALL/slamch.f b/INSTALL/slamch.f
new file mode 100644
index 00000000..abfb0eee
--- /dev/null
+++ b/INSTALL/slamch.f
@@ -0,0 +1,853 @@
+ REAL FUNCTION SLAMCH( CMACH )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ CHARACTER CMACH
+* ..
+*
+* Purpose
+* =======
+*
+* SLAMCH determines single precision machine parameters.
+*
+* Arguments
+* =========
+*
+* CMACH (input) CHARACTER*1
+* Specifies the value to be returned by SLAMCH:
+* = 'E' or 'e', SLAMCH := eps
+* = 'S' or 's , SLAMCH := sfmin
+* = 'B' or 'b', SLAMCH := base
+* = 'P' or 'p', SLAMCH := eps*base
+* = 'N' or 'n', SLAMCH := t
+* = 'R' or 'r', SLAMCH := rnd
+* = 'M' or 'm', SLAMCH := emin
+* = 'U' or 'u', SLAMCH := rmin
+* = 'L' or 'l', SLAMCH := emax
+* = 'O' or 'o', SLAMCH := rmax
+*
+* where
+*
+* eps = relative machine precision
+* sfmin = safe minimum, such that 1/sfmin does not overflow
+* base = base of the machine
+* prec = eps*base
+* t = number of (base) digits in the mantissa
+* rnd = 1.0 when rounding occurs in addition, 0.0 otherwise
+* emin = minimum exponent before (gradual) underflow
+* rmin = underflow threshold - base**(emin-1)
+* emax = largest exponent before overflow
+* rmax = overflow threshold - (base**emax)*(1-eps)
+*
+* =====================================================================
+*
+* .. Parameters ..
+ REAL ONE, ZERO
+ PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
+* ..
+* .. Local Scalars ..
+ LOGICAL FIRST, LRND
+ INTEGER BETA, IMAX, IMIN, IT
+ REAL BASE, EMAX, EMIN, EPS, PREC, RMACH, RMAX, RMIN,
+ $ RND, SFMIN, SMALL, T
+* ..
+* .. External Functions ..
+ LOGICAL LSAME
+ EXTERNAL LSAME
+* ..
+* .. External Subroutines ..
+ EXTERNAL SLAMC2
+* ..
+* .. Save statement ..
+ SAVE FIRST, EPS, SFMIN, BASE, T, RND, EMIN, RMIN,
+ $ EMAX, RMAX, PREC
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ CALL SLAMC2( BETA, IT, LRND, EPS, IMIN, RMIN, IMAX, RMAX )
+ BASE = BETA
+ T = IT
+ IF( LRND ) THEN
+ RND = ONE
+ EPS = ( BASE**( 1-IT ) ) / 2
+ ELSE
+ RND = ZERO
+ EPS = BASE**( 1-IT )
+ END IF
+ PREC = EPS*BASE
+ EMIN = IMIN
+ EMAX = IMAX
+ SFMIN = RMIN
+ SMALL = ONE / RMAX
+ IF( SMALL.GE.SFMIN ) THEN
+*
+* Use SMALL plus a bit, to avoid the possibility of rounding
+* causing overflow when computing 1/sfmin.
+*
+ SFMIN = SMALL*( ONE+EPS )
+ END IF
+ END IF
+*
+ IF( LSAME( CMACH, 'E' ) ) THEN
+ RMACH = EPS
+ ELSE IF( LSAME( CMACH, 'S' ) ) THEN
+ RMACH = SFMIN
+ ELSE IF( LSAME( CMACH, 'B' ) ) THEN
+ RMACH = BASE
+ ELSE IF( LSAME( CMACH, 'P' ) ) THEN
+ RMACH = PREC
+ ELSE IF( LSAME( CMACH, 'N' ) ) THEN
+ RMACH = T
+ ELSE IF( LSAME( CMACH, 'R' ) ) THEN
+ RMACH = RND
+ ELSE IF( LSAME( CMACH, 'M' ) ) THEN
+ RMACH = EMIN
+ ELSE IF( LSAME( CMACH, 'U' ) ) THEN
+ RMACH = RMIN
+ ELSE IF( LSAME( CMACH, 'L' ) ) THEN
+ RMACH = EMAX
+ ELSE IF( LSAME( CMACH, 'O' ) ) THEN
+ RMACH = RMAX
+ END IF
+*
+ SLAMCH = RMACH
+ FIRST = .FALSE.
+ RETURN
+*
+* End of SLAMCH
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE SLAMC1( BETA, T, RND, IEEE1 )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ LOGICAL IEEE1, RND
+ INTEGER BETA, T
+* ..
+*
+* Purpose
+* =======
+*
+* SLAMC1 determines the machine parameters given by BETA, T, RND, and
+* IEEE1.
+*
+* Arguments
+* =========
+*
+* BETA (output) INTEGER
+* The base of the machine.
+*
+* T (output) INTEGER
+* The number of ( BETA ) digits in the mantissa.
+*
+* RND (output) LOGICAL
+* Specifies whether proper rounding ( RND = .TRUE. ) or
+* chopping ( RND = .FALSE. ) occurs in addition. This may not
+* be a reliable guide to the way in which the machine performs
+* its arithmetic.
+*
+* IEEE1 (output) LOGICAL
+* Specifies whether rounding appears to be done in the IEEE
+* 'round to nearest' style.
+*
+* Further Details
+* ===============
+*
+* The routine is based on the routine ENVRON by Malcolm and
+* incorporates suggestions by Gentleman and Marovich. See
+*
+* Malcolm M. A. (1972) Algorithms to reveal properties of
+* floating-point arithmetic. Comms. of the ACM, 15, 949-951.
+*
+* Gentleman W. M. and Marovich S. B. (1974) More on algorithms
+* that reveal properties of floating point arithmetic units.
+* Comms. of the ACM, 17, 276-277.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ LOGICAL FIRST, LIEEE1, LRND
+ INTEGER LBETA, LT
+ REAL A, B, C, F, ONE, QTR, SAVEC, T1, T2
+* ..
+* .. External Functions ..
+ REAL SLAMC3
+ EXTERNAL SLAMC3
+* ..
+* .. Save statement ..
+ SAVE FIRST, LIEEE1, LBETA, LRND, LT
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ ONE = 1
+*
+* LBETA, LIEEE1, LT and LRND are the local values of BETA,
+* IEEE1, T and RND.
+*
+* Throughout this routine we use the function SLAMC3 to ensure
+* that relevant values are stored and not held in registers, or
+* are not affected by optimizers.
+*
+* Compute a = 2.0**m with the smallest positive integer m such
+* that
+*
+* fl( a + 1.0 ) = a.
+*
+ A = 1
+ C = 1
+*
+*+ WHILE( C.EQ.ONE )LOOP
+ 10 CONTINUE
+ IF( C.EQ.ONE ) THEN
+ A = 2*A
+ C = SLAMC3( A, ONE )
+ C = SLAMC3( C, -A )
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+* Now compute b = 2.0**m with the smallest positive integer m
+* such that
+*
+* fl( a + b ) .gt. a.
+*
+ B = 1
+ C = SLAMC3( A, B )
+*
+*+ WHILE( C.EQ.A )LOOP
+ 20 CONTINUE
+ IF( C.EQ.A ) THEN
+ B = 2*B
+ C = SLAMC3( A, B )
+ GO TO 20
+ END IF
+*+ END WHILE
+*
+* Now compute the base. a and c are neighbouring floating point
+* numbers in the interval ( beta**t, beta**( t + 1 ) ) and so
+* their difference is beta. Adding 0.25 to c is to ensure that it
+* is truncated to beta and not ( beta - 1 ).
+*
+ QTR = ONE / 4
+ SAVEC = C
+ C = SLAMC3( C, -A )
+ LBETA = C + QTR
+*
+* Now determine whether rounding or chopping occurs, by adding a
+* bit less than beta/2 and a bit more than beta/2 to a.
+*
+ B = LBETA
+ F = SLAMC3( B / 2, -B / 100 )
+ C = SLAMC3( F, A )
+ IF( C.EQ.A ) THEN
+ LRND = .TRUE.
+ ELSE
+ LRND = .FALSE.
+ END IF
+ F = SLAMC3( B / 2, B / 100 )
+ C = SLAMC3( F, A )
+ IF( ( LRND ) .AND. ( C.EQ.A ) )
+ $ LRND = .FALSE.
+*
+* Try and decide whether rounding is done in the IEEE 'round to
+* nearest' style. B/2 is half a unit in the last place of the two
+* numbers A and SAVEC. Furthermore, A is even, i.e. has last bit
+* zero, and SAVEC is odd. Thus adding B/2 to A should not change
+* A, but adding B/2 to SAVEC should change SAVEC.
+*
+ T1 = SLAMC3( B / 2, A )
+ T2 = SLAMC3( B / 2, SAVEC )
+ LIEEE1 = ( T1.EQ.A ) .AND. ( T2.GT.SAVEC ) .AND. LRND
+*
+* Now find the mantissa, t. It should be the integer part of
+* log to the base beta of a, however it is safer to determine t
+* by powering. So we find t as the smallest positive integer for
+* which
+*
+* fl( beta**t + 1.0 ) = 1.0.
+*
+ LT = 0
+ A = 1
+ C = 1
+*
+*+ WHILE( C.EQ.ONE )LOOP
+ 30 CONTINUE
+ IF( C.EQ.ONE ) THEN
+ LT = LT + 1
+ A = A*LBETA
+ C = SLAMC3( A, ONE )
+ C = SLAMC3( C, -A )
+ GO TO 30
+ END IF
+*+ END WHILE
+*
+ END IF
+*
+ BETA = LBETA
+ T = LT
+ RND = LRND
+ IEEE1 = LIEEE1
+ FIRST = .FALSE.
+ RETURN
+*
+* End of SLAMC1
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE SLAMC2( BETA, T, RND, EPS, EMIN, RMIN, EMAX, RMAX )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ LOGICAL RND
+ INTEGER BETA, EMAX, EMIN, T
+ REAL EPS, RMAX, RMIN
+* ..
+*
+* Purpose
+* =======
+*
+* SLAMC2 determines the machine parameters specified in its argument
+* list.
+*
+* Arguments
+* =========
+*
+* BETA (output) INTEGER
+* The base of the machine.
+*
+* T (output) INTEGER
+* The number of ( BETA ) digits in the mantissa.
+*
+* RND (output) LOGICAL
+* Specifies whether proper rounding ( RND = .TRUE. ) or
+* chopping ( RND = .FALSE. ) occurs in addition. This may not
+* be a reliable guide to the way in which the machine performs
+* its arithmetic.
+*
+* EPS (output) REAL
+* The smallest positive number such that
+*
+* fl( 1.0 - EPS ) .LT. 1.0,
+*
+* where fl denotes the computed value.
+*
+* EMIN (output) INTEGER
+* The minimum exponent before (gradual) underflow occurs.
+*
+* RMIN (output) REAL
+* The smallest normalized number for the machine, given by
+* BASE**( EMIN - 1 ), where BASE is the floating point value
+* of BETA.
+*
+* EMAX (output) INTEGER
+* The maximum exponent before overflow occurs.
+*
+* RMAX (output) REAL
+* The largest positive number for the machine, given by
+* BASE**EMAX * ( 1 - EPS ), where BASE is the floating point
+* value of BETA.
+*
+* Further Details
+* ===============
+*
+* The computation of EPS is based on a routine PARANOIA by
+* W. Kahan of the University of California at Berkeley.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ LOGICAL FIRST, IEEE, IWARN, LIEEE1, LRND
+ INTEGER GNMIN, GPMIN, I, LBETA, LEMAX, LEMIN, LT,
+ $ NGNMIN, NGPMIN
+ REAL A, B, C, HALF, LEPS, LRMAX, LRMIN, ONE, RBASE,
+ $ SIXTH, SMALL, THIRD, TWO, ZERO
+* ..
+* .. External Functions ..
+ REAL SLAMC3
+ EXTERNAL SLAMC3
+* ..
+* .. External Subroutines ..
+ EXTERNAL SLAMC1, SLAMC4, SLAMC5
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC ABS, MAX, MIN
+* ..
+* .. Save statement ..
+ SAVE FIRST, IWARN, LBETA, LEMAX, LEMIN, LEPS, LRMAX,
+ $ LRMIN, LT
+* ..
+* .. Data statements ..
+ DATA FIRST / .TRUE. / , IWARN / .FALSE. /
+* ..
+* .. Executable Statements ..
+*
+ IF( FIRST ) THEN
+ ZERO = 0
+ ONE = 1
+ TWO = 2
+*
+* LBETA, LT, LRND, LEPS, LEMIN and LRMIN are the local values of
+* BETA, T, RND, EPS, EMIN and RMIN.
+*
+* Throughout this routine we use the function SLAMC3 to ensure
+* that relevant values are stored and not held in registers, or
+* are not affected by optimizers.
+*
+* SLAMC1 returns the parameters LBETA, LT, LRND and LIEEE1.
+*
+ CALL SLAMC1( LBETA, LT, LRND, LIEEE1 )
+*
+* Start to find EPS.
+*
+ B = LBETA
+ A = B**( -LT )
+ LEPS = A
+*
+* Try some tricks to see whether or not this is the correct EPS.
+*
+ B = TWO / 3
+ HALF = ONE / 2
+ SIXTH = SLAMC3( B, -HALF )
+ THIRD = SLAMC3( SIXTH, SIXTH )
+ B = SLAMC3( THIRD, -HALF )
+ B = SLAMC3( B, SIXTH )
+ B = ABS( B )
+ IF( B.LT.LEPS )
+ $ B = LEPS
+*
+ LEPS = 1
+*
+*+ WHILE( ( LEPS.GT.B ).AND.( B.GT.ZERO ) )LOOP
+ 10 CONTINUE
+ IF( ( LEPS.GT.B ) .AND. ( B.GT.ZERO ) ) THEN
+ LEPS = B
+ C = SLAMC3( HALF*LEPS, ( TWO**5 )*( LEPS**2 ) )
+ C = SLAMC3( HALF, -C )
+ B = SLAMC3( HALF, C )
+ C = SLAMC3( HALF, -B )
+ B = SLAMC3( HALF, C )
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+ IF( A.LT.LEPS )
+ $ LEPS = A
+*
+* Computation of EPS complete.
+*
+* Now find EMIN. Let A = + or - 1, and + or - (1 + BASE**(-3)).
+* Keep dividing A by BETA until (gradual) underflow occurs. This
+* is detected when we cannot recover the previous A.
+*
+ RBASE = ONE / LBETA
+ SMALL = ONE
+ DO 20 I = 1, 3
+ SMALL = SLAMC3( SMALL*RBASE, ZERO )
+ 20 CONTINUE
+ A = SLAMC3( ONE, SMALL )
+ CALL SLAMC4( NGPMIN, ONE, LBETA )
+ CALL SLAMC4( NGNMIN, -ONE, LBETA )
+ CALL SLAMC4( GPMIN, A, LBETA )
+ CALL SLAMC4( GNMIN, -A, LBETA )
+ IEEE = .FALSE.
+*
+ IF( ( NGPMIN.EQ.NGNMIN ) .AND. ( GPMIN.EQ.GNMIN ) ) THEN
+ IF( NGPMIN.EQ.GPMIN ) THEN
+ LEMIN = NGPMIN
+* ( Non twos-complement machines, no gradual underflow;
+* e.g., VAX )
+ ELSE IF( ( GPMIN-NGPMIN ).EQ.3 ) THEN
+ LEMIN = NGPMIN - 1 + LT
+ IEEE = .TRUE.
+* ( Non twos-complement machines, with gradual underflow;
+* e.g., IEEE standard followers )
+ ELSE
+ LEMIN = MIN( NGPMIN, GPMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE IF( ( NGPMIN.EQ.GPMIN ) .AND. ( NGNMIN.EQ.GNMIN ) ) THEN
+ IF( ABS( NGPMIN-NGNMIN ).EQ.1 ) THEN
+ LEMIN = MAX( NGPMIN, NGNMIN )
+* ( Twos-complement machines, no gradual underflow;
+* e.g., CYBER 205 )
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE IF( ( ABS( NGPMIN-NGNMIN ).EQ.1 ) .AND.
+ $ ( GPMIN.EQ.GNMIN ) ) THEN
+ IF( ( GPMIN-MIN( NGPMIN, NGNMIN ) ).EQ.3 ) THEN
+ LEMIN = MAX( NGPMIN, NGNMIN ) - 1 + LT
+* ( Twos-complement machines with gradual underflow;
+* no known machine )
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+*
+ ELSE
+ LEMIN = MIN( NGPMIN, NGNMIN, GPMIN, GNMIN )
+* ( A guess; no known machine )
+ IWARN = .TRUE.
+ END IF
+ FIRST = .FALSE.
+***
+* Comment out this if block if EMIN is ok
+ IF( IWARN ) THEN
+ FIRST = .TRUE.
+ WRITE( 6, FMT = 9999 )LEMIN
+ END IF
+***
+*
+* Assume IEEE arithmetic if we found denormalised numbers above,
+* or if arithmetic seems to round in the IEEE style, determined
+* in routine SLAMC1. A true IEEE machine should have both things
+* true; however, faulty machines may have one or the other.
+*
+ IEEE = IEEE .OR. LIEEE1
+*
+* Compute RMIN by successive division by BETA. We could compute
+* RMIN as BASE**( EMIN - 1 ), but some machines underflow during
+* this computation.
+*
+ LRMIN = 1
+ DO 30 I = 1, 1 - LEMIN
+ LRMIN = SLAMC3( LRMIN*RBASE, ZERO )
+ 30 CONTINUE
+*
+* Finally, call SLAMC5 to compute EMAX and RMAX.
+*
+ CALL SLAMC5( LBETA, LT, LEMIN, IEEE, LEMAX, LRMAX )
+ END IF
+*
+ BETA = LBETA
+ T = LT
+ RND = LRND
+ EPS = LEPS
+ EMIN = LEMIN
+ RMIN = LRMIN
+ EMAX = LEMAX
+ RMAX = LRMAX
+*
+ RETURN
+*
+ 9999 FORMAT( / / ' WARNING. The value EMIN may be incorrect:-',
+ $ ' EMIN = ', I8, /
+ $ ' If, after inspection, the value EMIN looks',
+ $ ' acceptable please comment out ',
+ $ / ' the IF block as marked within the code of routine',
+ $ ' SLAMC2,', / ' otherwise supply EMIN explicitly.', / )
+*
+* End of SLAMC2
+*
+ END
+*
+************************************************************************
+*
+ REAL FUNCTION SLAMC3( A, B )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ REAL A, B
+* ..
+*
+* Purpose
+* =======
+*
+* SLAMC3 is intended to force A and B to be stored prior to doing
+* the addition of A and B , for use in situations where optimizers
+* might hold one of these in a register.
+*
+* Arguments
+* =========
+*
+* A (input) REAL
+* B (input) REAL
+* The values A and B.
+*
+* =====================================================================
+*
+* .. Executable Statements ..
+*
+ SLAMC3 = A + B
+*
+ RETURN
+*
+* End of SLAMC3
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE SLAMC4( EMIN, START, BASE )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ INTEGER BASE
+ INTEGER EMIN
+ REAL START
+* ..
+*
+* Purpose
+* =======
+*
+* SLAMC4 is a service routine for SLAMC2.
+*
+* Arguments
+* =========
+*
+* EMIN (output) INTEGER
+* The minimum exponent before (gradual) underflow, computed by
+* setting A = START and dividing by BASE until the previous A
+* can not be recovered.
+*
+* START (input) REAL
+* The starting point for determining EMIN.
+*
+* BASE (input) INTEGER
+* The base of the machine.
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ INTEGER I
+ REAL A, B1, B2, C1, C2, D1, D2, ONE, RBASE, ZERO
+* ..
+* .. External Functions ..
+ REAL SLAMC3
+ EXTERNAL SLAMC3
+* ..
+* .. Executable Statements ..
+*
+ A = START
+ ONE = 1
+ RBASE = ONE / BASE
+ ZERO = 0
+ EMIN = 1
+ B1 = SLAMC3( A*RBASE, ZERO )
+ C1 = A
+ C2 = A
+ D1 = A
+ D2 = A
+*+ WHILE( ( C1.EQ.A ).AND.( C2.EQ.A ).AND.
+* $ ( D1.EQ.A ).AND.( D2.EQ.A ) )LOOP
+ 10 CONTINUE
+ IF( ( C1.EQ.A ) .AND. ( C2.EQ.A ) .AND. ( D1.EQ.A ) .AND.
+ $ ( D2.EQ.A ) ) THEN
+ EMIN = EMIN - 1
+ A = B1
+ B1 = SLAMC3( A / BASE, ZERO )
+ C1 = SLAMC3( B1*BASE, ZERO )
+ D1 = ZERO
+ DO 20 I = 1, BASE
+ D1 = D1 + B1
+ 20 CONTINUE
+ B2 = SLAMC3( A*RBASE, ZERO )
+ C2 = SLAMC3( B2 / RBASE, ZERO )
+ D2 = ZERO
+ DO 30 I = 1, BASE
+ D2 = D2 + B2
+ 30 CONTINUE
+ GO TO 10
+ END IF
+*+ END WHILE
+*
+ RETURN
+*
+* End of SLAMC4
+*
+ END
+*
+************************************************************************
+*
+ SUBROUTINE SLAMC5( BETA, P, EMIN, IEEE, EMAX, RMAX )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ LOGICAL IEEE
+ INTEGER BETA, EMAX, EMIN, P
+ REAL RMAX
+* ..
+*
+* Purpose
+* =======
+*
+* SLAMC5 attempts to compute RMAX, the largest machine floating-point
+* number, without overflow. It assumes that EMAX + abs(EMIN) sum
+* approximately to a power of 2. It will fail on machines where this
+* assumption does not hold, for example, the Cyber 205 (EMIN = -28625,
+* EMAX = 28718). It will also fail if the value supplied for EMIN is
+* too large (i.e. too close to zero), probably with overflow.
+*
+* Arguments
+* =========
+*
+* BETA (input) INTEGER
+* The base of floating-point arithmetic.
+*
+* P (input) INTEGER
+* The number of base BETA digits in the mantissa of a
+* floating-point value.
+*
+* EMIN (input) INTEGER
+* The minimum exponent before (gradual) underflow.
+*
+* IEEE (input) LOGICAL
+* A logical flag specifying whether or not the arithmetic
+* system is thought to comply with the IEEE standard.
+*
+* EMAX (output) INTEGER
+* The largest exponent before overflow
+*
+* RMAX (output) REAL
+* The largest machine floating-point number.
+*
+* =====================================================================
+*
+* .. Parameters ..
+ REAL ZERO, ONE
+ PARAMETER ( ZERO = 0.0E0, ONE = 1.0E0 )
+* ..
+* .. Local Scalars ..
+ INTEGER EXBITS, EXPSUM, I, LEXP, NBITS, TRY, UEXP
+ REAL OLDY, RECBAS, Y, Z
+* ..
+* .. External Functions ..
+ REAL SLAMC3
+ EXTERNAL SLAMC3
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MOD
+* ..
+* .. Executable Statements ..
+*
+* First compute LEXP and UEXP, two powers of 2 that bound
+* abs(EMIN). We then assume that EMAX + abs(EMIN) will sum
+* approximately to the bound that is closest to abs(EMIN).
+* (EMAX is the exponent of the required number RMAX).
+*
+ LEXP = 1
+ EXBITS = 1
+ 10 CONTINUE
+ TRY = LEXP*2
+ IF( TRY.LE.( -EMIN ) ) THEN
+ LEXP = TRY
+ EXBITS = EXBITS + 1
+ GO TO 10
+ END IF
+ IF( LEXP.EQ.-EMIN ) THEN
+ UEXP = LEXP
+ ELSE
+ UEXP = TRY
+ EXBITS = EXBITS + 1
+ END IF
+*
+* Now -LEXP is less than or equal to EMIN, and -UEXP is greater
+* than or equal to EMIN. EXBITS is the number of bits needed to
+* store the exponent.
+*
+ IF( ( UEXP+EMIN ).GT.( -LEXP-EMIN ) ) THEN
+ EXPSUM = 2*LEXP
+ ELSE
+ EXPSUM = 2*UEXP
+ END IF
+*
+* EXPSUM is the exponent range, approximately equal to
+* EMAX - EMIN + 1 .
+*
+ EMAX = EXPSUM + EMIN - 1
+ NBITS = 1 + EXBITS + P
+*
+* NBITS is the total number of bits needed to store a
+* floating-point number.
+*
+ IF( ( MOD( NBITS, 2 ).EQ.1 ) .AND. ( BETA.EQ.2 ) ) THEN
+*
+* Either there are an odd number of bits used to store a
+* floating-point number, which is unlikely, or some bits are
+* not used in the representation of numbers, which is possible,
+* (e.g. Cray machines) or the mantissa has an implicit bit,
+* (e.g. IEEE machines, Dec Vax machines), which is perhaps the
+* most likely. We have to assume the last alternative.
+* If this is true, then we need to reduce EMAX by one because
+* there must be some way of representing zero in an implicit-bit
+* system. On machines like Cray, we are reducing EMAX by one
+* unnecessarily.
+*
+ EMAX = EMAX - 1
+ END IF
+*
+ IF( IEEE ) THEN
+*
+* Assume we are on an IEEE machine which reserves one exponent
+* for infinity and NaN.
+*
+ EMAX = EMAX - 1
+ END IF
+*
+* Now create RMAX, the largest machine number, which should
+* be equal to (1.0 - BETA**(-P)) * BETA**EMAX .
+*
+* First compute 1.0 - BETA**(-P), being careful that the
+* result is less than 1.0 .
+*
+ RECBAS = ONE / BETA
+ Z = BETA - ONE
+ Y = ZERO
+ DO 20 I = 1, P
+ Z = Z*RECBAS
+ IF( Y.LT.ONE )
+ $ OLDY = Y
+ Y = SLAMC3( Y, Z )
+ 20 CONTINUE
+ IF( Y.GE.ONE )
+ $ Y = OLDY
+*
+* Now multiply by BETA**EMAX to get RMAX.
+*
+ DO 30 I = 1, EMAX
+ Y = SLAMC3( Y*BETA, ZERO )
+ 30 CONTINUE
+*
+ RMAX = Y
+ RETURN
+*
+* End of SLAMC5
+*
+ END
diff --git a/INSTALL/slamchtst.f b/INSTALL/slamchtst.f
new file mode 100644
index 00000000..256aaa6c
--- /dev/null
+++ b/INSTALL/slamchtst.f
@@ -0,0 +1,40 @@
+ PROGRAM TEST2
+*
+* -- LAPACK test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Local Scalars ..
+ REAL BASE, EMAX, EMIN, EPS, RMAX, RMIN, RND, SFMIN,
+ $ T, PREC
+* ..
+* .. External Functions ..
+ REAL SLAMCH
+ EXTERNAL SLAMCH
+* ..
+* .. Executable Statements ..
+*
+ EPS = SLAMCH( 'Epsilon' )
+ SFMIN = SLAMCH( 'Safe minimum' )
+ BASE = SLAMCH( 'Base' )
+ PREC = SLAMCH( 'Precision' )
+ T = SLAMCH( 'Number of digits in mantissa' )
+ RND = SLAMCH( 'Rounding mode' )
+ EMIN = SLAMCH( 'Minimum exponent' )
+ RMIN = SLAMCH( 'Underflow threshold' )
+ EMAX = SLAMCH( 'Largest exponent' )
+ RMAX = SLAMCH( 'Overflow threshold' )
+*
+ WRITE( 6, * )' Epsilon = ', EPS
+ WRITE( 6, * )' Safe minimum = ', SFMIN
+ WRITE( 6, * )' Base = ', BASE
+ WRITE( 6, * )' Precision = ', PREC
+ WRITE( 6, * )' Number of digits in mantissa = ', T
+ WRITE( 6, * )' Rounding mode = ', RND
+ WRITE( 6, * )' Minimum exponent = ', EMIN
+ WRITE( 6, * )' Underflow threshold = ', RMIN
+ WRITE( 6, * )' Largest exponent = ', EMAX
+ WRITE( 6, * )' Overflow threshold = ', RMAX
+ WRITE( 6, * )' Reciprocal of safe minimum = ', 1 / SFMIN
+*
+ END
diff --git a/INSTALL/tstiee.f b/INSTALL/tstiee.f
new file mode 100644
index 00000000..f837e54a
--- /dev/null
+++ b/INSTALL/tstiee.f
@@ -0,0 +1,750 @@
+ PROGRAM MAIN
+*
+* -- LAPACK test routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. External Functions ..
+ INTEGER ILAENV
+ EXTERNAL ILAENV
+* ..
+* .. Local Scalars ..
+ INTEGER IEEEOK
+* ..
+* .. Executable Statements ..
+*
+ WRITE( 6, FMT = * )
+ $ 'We are about to check whether infinity arithmetic'
+ WRITE( 6, FMT = * )'can be trusted. If this test hangs, set'
+ WRITE( 6, FMT = * )
+ $ 'ILAENV = 0 for ISPEC = 10 in LAPACK/SRC/ilaenv.f'
+*
+ IEEEOK = ILAENV( 10, 'ILAENV', 'N', 1, 2, 3, 4 )
+ WRITE( 6, FMT = * )
+*
+ IF( IEEEOK.EQ.0 ) THEN
+ WRITE( 6, FMT = * )
+ $ 'Infinity arithmetic did not perform per the ieee spec'
+ ELSE
+ WRITE( 6, FMT = * )
+ $ 'Infinity arithmetic performed as per the ieee spec.'
+ WRITE( 6, FMT = * )
+ $ 'However, this is not an exhaustive test and does not'
+ WRITE( 6, FMT = * )
+ $ 'guarantee that infinity arithmetic meets the',
+ $ ' ieee spec.'
+ END IF
+*
+ WRITE( 6, FMT = * )
+ WRITE( 6, FMT = * )
+ $ 'We are about to check whether NaN arithmetic'
+ WRITE( 6, FMT = * )'can be trusted. If this test hangs, set'
+ WRITE( 6, FMT = * )
+ $ 'ILAENV = 0 for ISPEC = 11 in LAPACK/SRC/ilaenv.f'
+ IEEEOK = ILAENV( 11, 'ILAENV', 'N', 1, 2, 3, 4 )
+*
+ WRITE( 6, FMT = * )
+ IF( IEEEOK.EQ.0 ) THEN
+ WRITE( 6, FMT = * )
+ $ 'NaN arithmetic did not perform per the ieee spec'
+ ELSE
+ WRITE( 6, FMT = * )'NaN arithmetic performed as per the ieee',
+ $ ' spec.'
+ WRITE( 6, FMT = * )
+ $ 'However, this is not an exhaustive test and does not'
+ WRITE( 6, FMT = * )'guarantee that NaN arithmetic meets the',
+ $ ' ieee spec.'
+ END IF
+ WRITE( 6, FMT = * )
+*
+ END
+ INTEGER FUNCTION ILAENV( ISPEC, NAME, OPTS, N1, N2, N3,
+ $ N4 )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ CHARACTER*( * ) NAME, OPTS
+ INTEGER ISPEC, N1, N2, N3, N4
+* ..
+*
+* Purpose
+* =======
+*
+* ILAENV is called from the LAPACK routines to choose problem-dependent
+* parameters for the local environment. See ISPEC for a description of
+* the parameters.
+*
+* This version provides a set of parameters which should give good,
+* but not optimal, performance on many of the currently available
+* computers. Users are encouraged to modify this subroutine to set
+* the tuning parameters for their particular machine using the option
+* and problem size information in the arguments.
+*
+* This routine will not function correctly if it is converted to all
+* lower case. Converting it to all upper case is allowed.
+*
+* Arguments
+* =========
+*
+* ISPEC (input) INTEGER
+* Specifies the parameter to be returned as the value of
+* ILAENV.
+* = 1: the optimal blocksize; if this value is 1, an unblocked
+* algorithm will give the best performance.
+* = 2: the minimum block size for which the block routine
+* should be used; if the usable block size is less than
+* this value, an unblocked routine should be used.
+* = 3: the crossover point (in a block routine, for N less
+* than this value, an unblocked routine should be used)
+* = 4: the number of shifts, used in the nonsymmetric
+* eigenvalue routines
+* = 5: the minimum column dimension for blocking to be used;
+* rectangular blocks must have dimension at least k by m,
+* where k is given by ILAENV(2,...) and m by ILAENV(5,...)
+* = 6: the crossover point for the SVD (when reducing an m by n
+* matrix to bidiagonal form, if max(m,n)/min(m,n) exceeds
+* this value, a QR factorization is used first to reduce
+* the matrix to a triangular form.)
+* = 7: the number of processors
+* = 8: the crossover point for the multishift QR and QZ methods
+* for nonsymmetric eigenvalue problems.
+* = 9: maximum size of the subproblems at the bottom of the
+* computation tree in the divide-and-conquer algorithm
+* (used by xGELSD and xGESDD)
+* =10: ieee NaN arithmetic can be trusted not to trap
+* =11: infinity arithmetic can be trusted not to trap
+*
+* NAME (input) CHARACTER*(*)
+* The name of the calling subroutine, in either upper case or
+* lower case.
+*
+* OPTS (input) CHARACTER*(*)
+* The character options to the subroutine NAME, concatenated
+* into a single character string. For example, UPLO = 'U',
+* TRANS = 'T', and DIAG = 'N' for a triangular routine would
+* be specified as OPTS = 'UTN'.
+*
+* N1 (input) INTEGER
+* N2 (input) INTEGER
+* N3 (input) INTEGER
+* N4 (input) INTEGER
+* Problem dimensions for the subroutine NAME; these may not all
+* be required.
+*
+* (ILAENV) (output) INTEGER
+* >= 0: the value of the parameter specified by ISPEC
+* < 0: if ILAENV = -k, the k-th argument had an illegal value.
+*
+* Further Details
+* ===============
+*
+* The following conventions have been used when calling ILAENV from the
+* LAPACK routines:
+* 1) OPTS is a concatenation of all of the character options to
+* subroutine NAME, in the same order that they appear in the
+* argument list for NAME, even if they are not used in determining
+* the value of the parameter specified by ISPEC.
+* 2) The problem dimensions N1, N2, N3, N4 are specified in the order
+* that they appear in the argument list for NAME. N1 is used
+* first, N2 second, and so on, and unused problem dimensions are
+* passed a value of -1.
+* 3) The parameter value returned by ILAENV is checked for validity in
+* the calling subroutine. For example, ILAENV is used to retrieve
+* the optimal blocksize for STRTRI as follows:
+*
+* NB = ILAENV( 1, 'STRTRI', UPLO // DIAG, N, -1, -1, -1 )
+* IF( NB.LE.1 ) NB = MAX( 1, N )
+*
+* =====================================================================
+*
+* .. Local Scalars ..
+ LOGICAL CNAME, SNAME
+ CHARACTER*1 C1
+ CHARACTER*2 C2, C4
+ CHARACTER*3 C3
+ CHARACTER*6 SUBNAM
+ INTEGER I, IC, IZ, NB, NBMIN, NX
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC CHAR, ICHAR, INT, MIN, REAL
+* ..
+* .. External Functions ..
+ INTEGER IEEECK
+ EXTERNAL IEEECK
+* ..
+* .. Executable Statements ..
+*
+ GO TO ( 100, 100, 100, 400, 500, 600, 700, 800, 900, 1000,
+ $ 1100 ) ISPEC
+*
+* Invalid value for ISPEC
+*
+ ILAENV = -1
+ RETURN
+*
+ 100 CONTINUE
+*
+* Convert NAME to upper case if the first character is lower case.
+*
+ ILAENV = 1
+ SUBNAM = NAME
+ IC = ICHAR( SUBNAM( 1:1 ) )
+ IZ = ICHAR( 'Z' )
+ IF( IZ.EQ.90 .OR. IZ.EQ.122 ) THEN
+*
+* ASCII character set
+*
+ IF( IC.GE.97 .AND. IC.LE.122 ) THEN
+ SUBNAM( 1:1 ) = CHAR( IC-32 )
+ DO 10 I = 2, 6
+ IC = ICHAR( SUBNAM( I:I ) )
+ IF( IC.GE.97 .AND. IC.LE.122 )
+ $ SUBNAM( I:I ) = CHAR( IC-32 )
+ 10 CONTINUE
+ END IF
+*
+ ELSE IF( IZ.EQ.233 .OR. IZ.EQ.169 ) THEN
+*
+* EBCDIC character set
+*
+ IF( ( IC.GE.129 .AND. IC.LE.137 ) .OR.
+ $ ( IC.GE.145 .AND. IC.LE.153 ) .OR.
+ $ ( IC.GE.162 .AND. IC.LE.169 ) ) THEN
+ SUBNAM( 1:1 ) = CHAR( IC+64 )
+ DO 20 I = 2, 6
+ IC = ICHAR( SUBNAM( I:I ) )
+ IF( ( IC.GE.129 .AND. IC.LE.137 ) .OR.
+ $ ( IC.GE.145 .AND. IC.LE.153 ) .OR.
+ $ ( IC.GE.162 .AND. IC.LE.169 ) )
+ $ SUBNAM( I:I ) = CHAR( IC+64 )
+ 20 CONTINUE
+ END IF
+*
+ ELSE IF( IZ.EQ.218 .OR. IZ.EQ.250 ) THEN
+*
+* Prime machines: ASCII+128
+*
+ IF( IC.GE.225 .AND. IC.LE.250 ) THEN
+ SUBNAM( 1:1 ) = CHAR( IC-32 )
+ DO 30 I = 2, 6
+ IC = ICHAR( SUBNAM( I:I ) )
+ IF( IC.GE.225 .AND. IC.LE.250 )
+ $ SUBNAM( I:I ) = CHAR( IC-32 )
+ 30 CONTINUE
+ END IF
+ END IF
+*
+ C1 = SUBNAM( 1:1 )
+ SNAME = C1.EQ.'S' .OR. C1.EQ.'D'
+ CNAME = C1.EQ.'C' .OR. C1.EQ.'Z'
+ IF( .NOT.( CNAME .OR. SNAME ) )
+ $ RETURN
+ C2 = SUBNAM( 2:3 )
+ C3 = SUBNAM( 4:6 )
+ C4 = C3( 2:3 )
+*
+ GO TO ( 110, 200, 300 ) ISPEC
+*
+ 110 CONTINUE
+*
+* ISPEC = 1: block size
+*
+* In these examples, separate code is provided for setting NB for
+* real and complex. We assume that NB will take the same value in
+* single or double precision.
+*
+ NB = 1
+*
+ IF( C2.EQ.'GE' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ ELSE IF( C3.EQ.'QRF' .OR. C3.EQ.'RQF' .OR. C3.EQ.'LQF' .OR.
+ $ C3.EQ.'QLF' ) THEN
+ IF( SNAME ) THEN
+ NB = 32
+ ELSE
+ NB = 32
+ END IF
+ ELSE IF( C3.EQ.'HRD' ) THEN
+ IF( SNAME ) THEN
+ NB = 32
+ ELSE
+ NB = 32
+ END IF
+ ELSE IF( C3.EQ.'BRD' ) THEN
+ IF( SNAME ) THEN
+ NB = 32
+ ELSE
+ NB = 32
+ END IF
+ ELSE IF( C3.EQ.'TRI' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'PO' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'SY' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ ELSE IF( SNAME .AND. C3.EQ.'TRD' ) THEN
+ NB = 32
+ ELSE IF( SNAME .AND. C3.EQ.'GST' ) THEN
+ NB = 64
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'HE' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ NB = 64
+ ELSE IF( C3.EQ.'TRD' ) THEN
+ NB = 32
+ ELSE IF( C3.EQ.'GST' ) THEN
+ NB = 64
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'OR' ) THEN
+ IF( C3( 1:1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NB = 32
+ END IF
+ ELSE IF( C3( 1:1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NB = 32
+ END IF
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'UN' ) THEN
+ IF( C3( 1:1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NB = 32
+ END IF
+ ELSE IF( C3( 1:1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NB = 32
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'GB' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ IF( N4.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ ELSE
+ IF( N4.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'PB' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ IF( N2.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ ELSE
+ IF( N2.LE.64 ) THEN
+ NB = 1
+ ELSE
+ NB = 32
+ END IF
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'TR' ) THEN
+ IF( C3.EQ.'TRI' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'LA' ) THEN
+ IF( C3.EQ.'UUM' ) THEN
+ IF( SNAME ) THEN
+ NB = 64
+ ELSE
+ NB = 64
+ END IF
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'ST' ) THEN
+ IF( C3.EQ.'EBZ' ) THEN
+ NB = 1
+ END IF
+ END IF
+ ILAENV = NB
+ RETURN
+*
+ 200 CONTINUE
+*
+* ISPEC = 2: minimum block size
+*
+ NBMIN = 2
+ IF( C2.EQ.'GE' ) THEN
+ IF( C3.EQ.'QRF' .OR. C3.EQ.'RQF' .OR. C3.EQ.'LQF' .OR.
+ $ C3.EQ.'QLF' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ ELSE IF( C3.EQ.'HRD' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ ELSE IF( C3.EQ.'BRD' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ ELSE IF( C3.EQ.'TRI' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 2
+ ELSE
+ NBMIN = 2
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'SY' ) THEN
+ IF( C3.EQ.'TRF' ) THEN
+ IF( SNAME ) THEN
+ NBMIN = 8
+ ELSE
+ NBMIN = 8
+ END IF
+ ELSE IF( SNAME .AND. C3.EQ.'TRD' ) THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'HE' ) THEN
+ IF( C3.EQ.'TRD' ) THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'OR' ) THEN
+ IF( C3( 1:1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( C3( 1:1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NBMIN = 2
+ END IF
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'UN' ) THEN
+ IF( C3( 1:1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NBMIN = 2
+ END IF
+ ELSE IF( C3( 1:1 ).EQ.'M' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NBMIN = 2
+ END IF
+ END IF
+ END IF
+ ILAENV = NBMIN
+ RETURN
+*
+ 300 CONTINUE
+*
+* ISPEC = 3: crossover point
+*
+ NX = 0
+ IF( C2.EQ.'GE' ) THEN
+ IF( C3.EQ.'QRF' .OR. C3.EQ.'RQF' .OR. C3.EQ.'LQF' .OR.
+ $ C3.EQ.'QLF' ) THEN
+ IF( SNAME ) THEN
+ NX = 128
+ ELSE
+ NX = 128
+ END IF
+ ELSE IF( C3.EQ.'HRD' ) THEN
+ IF( SNAME ) THEN
+ NX = 128
+ ELSE
+ NX = 128
+ END IF
+ ELSE IF( C3.EQ.'BRD' ) THEN
+ IF( SNAME ) THEN
+ NX = 128
+ ELSE
+ NX = 128
+ END IF
+ END IF
+ ELSE IF( C2.EQ.'SY' ) THEN
+ IF( SNAME .AND. C3.EQ.'TRD' ) THEN
+ NX = 32
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'HE' ) THEN
+ IF( C3.EQ.'TRD' ) THEN
+ NX = 32
+ END IF
+ ELSE IF( SNAME .AND. C2.EQ.'OR' ) THEN
+ IF( C3( 1:1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NX = 128
+ END IF
+ END IF
+ ELSE IF( CNAME .AND. C2.EQ.'UN' ) THEN
+ IF( C3( 1:1 ).EQ.'G' ) THEN
+ IF( C4.EQ.'QR' .OR. C4.EQ.'RQ' .OR. C4.EQ.'LQ' .OR.
+ $ C4.EQ.'QL' .OR. C4.EQ.'HR' .OR. C4.EQ.'TR' .OR.
+ $ C4.EQ.'BR' ) THEN
+ NX = 128
+ END IF
+ END IF
+ END IF
+ ILAENV = NX
+ RETURN
+*
+ 400 CONTINUE
+*
+* ISPEC = 4: number of shifts (used by xHSEQR)
+*
+ ILAENV = 6
+ RETURN
+*
+ 500 CONTINUE
+*
+* ISPEC = 5: minimum column dimension (not used)
+*
+ ILAENV = 2
+ RETURN
+*
+ 600 CONTINUE
+*
+* ISPEC = 6: crossover point for SVD (used by xGELSS and xGESVD)
+*
+ ILAENV = INT( REAL( MIN( N1, N2 ) )*1.6E0 )
+ RETURN
+*
+ 700 CONTINUE
+*
+* ISPEC = 7: number of processors (not used)
+*
+ ILAENV = 1
+ RETURN
+*
+ 800 CONTINUE
+*
+* ISPEC = 8: crossover point for multishift (used by xHSEQR)
+*
+ ILAENV = 50
+ RETURN
+*
+ 900 CONTINUE
+*
+* ISPEC = 9: maximum size of the subproblems at the bottom of the
+* computation tree in the divide-and-conquer algorithm
+* (used by xGELSD and xGESDD)
+*
+ ILAENV = 25
+ RETURN
+*
+ 1000 CONTINUE
+*
+* ISPEC = 10: ieee NaN arithmetic can be trusted not to trap
+*
+ ILAENV = 1
+ IF (ILAENV .EQ. 1) THEN
+ ILAENV = IEEECK( 0, 0.0, 1.0 )
+ ENDIF
+ RETURN
+*
+ 1100 CONTINUE
+*
+* ISPEC = 11: infinity arithmetic can be trusted not to trap
+*
+ ILAENV = 1
+ IF (ILAENV .EQ. 1) THEN
+ ILAENV = IEEECK( 1, 0.0, 1.0 )
+ ENDIF
+ RETURN
+*
+* End of ILAENV
+*
+ END
+ INTEGER FUNCTION IEEECK( ISPEC, ZERO, ONE )
+*
+* -- LAPACK auxiliary routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ INTEGER ISPEC
+ REAL ZERO, ONE
+* ..
+*
+* Purpose
+* =======
+*
+* IEEECK is called from the ILAENV to verify that Inifinity and
+* possibly NaN arithmetic is safe (i.e. will not trap).
+*
+* Arguments
+* =========
+*
+* ISPEC (input) INTEGER
+* Specifies whether to test just for inifinity arithmetic
+* or whether to test for infinity and NaN arithmetic.
+* = 0: Verify infinity arithmetic only.
+* = 1: Verify infinity and NaN arithmetic.
+*
+* ZERO (input) REAL
+* Must contain the value 0.0
+* This is passed to prevent the compiler from optimizing
+* away this code.
+*
+* ONE (input) REAL
+* Must contain the value 1.0
+* This is passed to prevent the compiler from optimizing
+* away this code.
+*
+* RETURN VALUE: INTEGER
+* = 0: Arithmetic failed to produce the correct answers
+* = 1: Arithmetic produced the correct answers
+*
+* .. Local Scalars ..
+ REAL POSINF, NEGINF, NAN1, NAN2, NAN3, NAN4, NAN5, NAN6, NEGZRO,
+ $ NEWZRO
+* ..
+* .. Executable Statements ..
+ IEEECK = 1
+
+ POSINF = ONE /ZERO
+ IF ( POSINF .LE. ONE ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ NEGINF = -ONE / ZERO
+ IF ( NEGINF .GE. ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ NEGZRO = ONE / ( NEGINF + ONE )
+ IF ( NEGZRO .NE. ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ NEGINF = ONE / NEGZRO
+ IF ( NEGINF .GE. ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ NEWZRO = NEGZRO + ZERO
+ IF ( NEWZRO .NE. ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ POSINF = ONE / NEWZRO
+ IF ( POSINF .LE. ONE ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ NEGINF = NEGINF * POSINF
+ IF ( NEGINF .GE. ZERO ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ POSINF = POSINF * POSINF
+ IF ( POSINF .LE. ONE ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+
+
+*
+* Return if we were only asked to check infinity arithmetic
+*
+ IF (ISPEC .EQ. 0 ) RETURN
+
+ NAN1 = POSINF + NEGINF
+
+ NAN2 = POSINF / NEGINF
+
+ NAN3 = POSINF / POSINF
+
+ NAN4 = POSINF * ZERO
+
+ NAN5 = NEGINF * NEGZRO
+
+ NAN6 = NAN5 * 0.0
+
+ IF ( NAN1 .EQ. NAN1 ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ IF ( NAN2 .EQ. NAN2 ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ IF ( NAN3 .EQ. NAN3 ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ IF ( NAN4 .EQ. NAN4 ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ IF ( NAN5 .EQ. NAN5 ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ IF ( NAN6 .EQ. NAN6 ) THEN
+ IEEECK = 0
+ RETURN
+ ENDIF
+
+ RETURN
+ END