From: Robert E. Brown
Subject: Re: I'm not the only one who values interval-arithmetic
Date: 
Message-ID: <87llsq9b29.fsf@loki.bibliotech.com>
I'd like to send Robert Mass some Common Lisp interval arithmetic code, but
his postings don't seem to include his email address.  Anyone know it?

Just in case the headers on this post are messed up ... my email address is
bbrown at speakeasy.net.

                        bob

From: ··········@YahooGroups.Com
Subject: Re: I'm not the only one who values interval-arithmetic
Date: 
Message-ID: <REM-2004apr18-002@Yahoo.Com>
> Date: 14 Sep 2003 19:58:54 -0400
> From: ······@speakeasy.net (Robert E. Brown)
> I'd like to send Robert Mass some Common Lisp interval arithmetic
> code, but his postings don't seem to include his email address.
> Anyone know it?

If you're talking about me, you misspelled my name, so your article
didn't turn up when I Google-searched for my name to see where people
were talking about me. Also, my public e-mail address is the one in
this article. It's spam protected via needing to manually join the
Yahoo Group before you can send me e-mail via that address. Previously
I posted under several of my regular Yahoo! Mail addresses, and a
previous ISP e-mail address, and without exception those addresses got
so full of spam as to be unusable. So perhaps you can understand my
paranoid about revealing yet another ISP or Yanoo! Mail address in
public only to see it spammed to death just like the others.

Also, please don't send program source to me by e-mail. Instead, post
it in some accessible place, then e-mail me just a brief description
and the URL where I can look at it and optionally fetch it *after* I
decide it would be of value to me.

Also, do you have a plain-text file (or simple HTML document without
any frames or images or graphics or unicode or javascript or applets
etc.; my only Web access from home is via VT100 emulator into Unix
shell and then from there to the Web using lynx) which shows some
canned demos to give an idea what your software can do? For example,
see the demos of the interval-arithmetic software I wrote myself (see
article I posted about an hour ago in this same thread). How does your
software compare with mine?
From: Robert E. Brown
Subject: Re: I'm not the only one who values interval-arithmetic
Date: 
Message-ID: <87oepo3b0e.fsf@loki.bibliotech.com>
This post is mostly for Robert Maas, who seems unreachable by email.  Maybe
others will find it interesting too.

Several months ago I discovered affine arithmetic, an alternative to
interval arithmetic.  After reading a paper about it, I spent a few days
experimenting with both interval arithmetic and affine arithmetic.  Enclosed
is a copy of some interval code I wrote.

The package was written for SBCL and uses some non-standard features to
change floating point rounding modes.  It's far from perfect, but I did try
to comment some of the defects in the code.  Search for XXXX to find them.

The file nasty.lisp below is the Lisp code for the classic Rump polynomial
that blows up when evaluated using double precision floating point.  If you
use the interval code to generate arguments for the function f, the interval
result diverges:

    * (load "interval.lisp")

    T
    * (in-package "IA")

    #<PACKAGE "INTERVAL-ARITH">

    * (load "nasty.lisp")

    <<< output deleted >>>

    * (f1  (number-to-interval 77617) (number-to-interval 33096))

    #<INTERVAL [-8.239729e+30, 8.2397294e+30] {9293C61}>



========================================
interval.lisp
========================================

;;; -*- mode: lisp; package: scapegoat -*-

;;;     Interval arithmetic

;; Copyright (C) 2003, Robert E. Brown.


(in-package "CL-USER")

(defpackage "INTERVAL-ARITH"
  (:nicknames "IA")
  (:documentation "Interval arithmetic")
  (:shadow cl:+ cl:- cl:* cl:/
           cl:= cl:< cl:<= cl:> cl:>=
           cl:abs cl:sqrt cl:zerop)
  (:use COMMON-LISP)
  (:export "INTERVAL" "LOW" "HIGH" "MAKE-INTERVAL"
           "NUMBER-TO-INTERVAL" "FUZZY-NUMBER-TO-INTERVAL"
           "+" "-" "*" "/"
           "=" "<" "<=" ">" ">="
           "ABS" "SQRT" "ZEROP"))

(in-package "IA")

(declaim (optimize (debug 3) (safety 3) (speed 0)))


(eval-when (:execute :load-toplevel :compile-toplevel)

(defmacro with-negative-rounding (&body body)
  (let ((old-modes (gensym "old-modes"))
        (new-modes (gensym "new-modes")))
    `(let* ((,old-modes (sb-vm::floating-point-modes)))
      (unwind-protect
           (let ((,new-modes ,old-modes))
             (setf (ldb sb-vm::float-rounding-mode ,new-modes)
                   sb-vm::float-round-to-negative)
             (setf (sb-vm::floating-point-modes) ,new-modes)
             ,@body)
        (setf (sb-vm::floating-point-modes) ,old-modes)))))

(defmacro with-positive-rounding (&body body)
  (let ((old-modes (gensym "old-modes"))
        (new-modes (gensym "new-modes")))
    `(let* ((,old-modes (sb-vm::floating-point-modes)))
      (unwind-protect
           (let ((,new-modes ,old-modes))
             (setf (ldb sb-vm::float-rounding-mode ,new-modes)
                   sb-vm::float-round-to-positive)
             (setf (sb-vm::floating-point-modes) ,new-modes)
             ,@body)
        (setf (sb-vm::floating-point-modes) ,old-modes)))))


;; Choose one of these as the type of interval upper and lower bounds.

(deftype interval-bound () 'single-float)
;(deftype interval-bound () 'double-float)

(defmacro zero-bound ()
  "Zero of the appropriate type for use as the bound of an interval"
 (coerce 0 'interval-bound))


(defclass interval ()
  ((low :accessor low
        :initform (error "interval :LOW slot not initialized")
        :initarg :low
        :type interval-bound)
   (high :accessor high
         :initform (error "interval :HIGH slot not initialized")
         :initarg :high
         :type interval-bound))
  (:documentation "A floating point interval"))

) ; end of eval-when


(defun make-interval (low high)
  (declare (type interval-bound low high))
  "Create an interval representing the range LOW to HIGH."
  (assert (cl:<= low high))
  (make-instance 'interval :low low :high high))

(defmethod print-object ((interval interval) (stream stream))
  (print-unreadable-object (interval stream :type t :identity t)
    (format stream "[~A, ~A]" (low interval) (high interval)))
  (values))


(defun number-to-interval (x)
  (declare (type number x))
  ;; XXXX: The conversion of x to interval bounds should be done twice,
  ;; rounding down to create the lower bound and up to create the high
  ;; bound.
  (let ((bound (coerce x 'interval-bound)))
    (make-interval bound bound)))

(defun fuzzy-number-to-interval (x epsilon)
  (declare (type float x epsilon))
  (let ((center (coerce x 'interval-bound))
        (radius (coerce epsilon 'interval-bound)))
    (if (cl:zerop radius)
        (make-interval center center)
        (make-interval (with-negative-rounding (cl:- center radius))
                       (with-positive-rounding (cl:+ center radius))))))


(defvar +zero-interval+ (number-to-interval 0)
  "The interval containing only zero")


(defun interval-zerop (x)
  (and (cl:zerop (the interval-bound (low x)))
       (cl:zerop (the interval-bound (high x)))))

(defgeneric zerop (x)
  (:documentation "Is X equal to zero?")
  (:method ((x number)) (cl:zerop x))
  (:method ((x interval)) (interval-zerop x)))


(defgeneric + (x y)
  (:documentation "Add X and Y")
  (:method ((x number) (y number)) (cl:+ x y))
  (:method ((x float) (y number)) (number-to-interval (cl:+ x y)))
  (:method ((x number) (y float)) (number-to-interval (cl:+ x y)))
  (:method ((x interval) (y number)) (+ x (number-to-interval y)))
  (:method ((x number) (y interval)) (+ (number-to-interval x) y))
  (:method ((x interval) (y interval))
    (let ((xl (low x))
          (xh (high x))
          (yl (low y))
          (yh (high y)))
      (declare (type interval-bound xl xh yl yh))
      (make-interval (with-negative-rounding (cl:+ xl yl))
                     (with-positive-rounding (cl:+ xh yh))))))

(defgeneric - (x y)
  (:documentation "Subtract Y from X")
  (:method ((x number) (y number)) (cl:- x y))
  (:method ((x float) (y number)) (number-to-interval (cl:- x y)))
  (:method ((x number) (y float)) (number-to-interval (cl:- x y)))
  (:method ((x interval) (y number)) (- x (number-to-interval y)))
  (:method ((x number) (y interval)) (- (number-to-interval x) y))
  (:method ((x interval) (y interval))
    (let ((xl (low x))
          (xh (high x))
          (yl (low y))
          (yh (high y)))
      (declare (type interval-bound xl xh yl yh))
      (make-interval (with-negative-rounding (cl:- xl yh))
                     (with-positive-rounding (cl:- xh yl))))))

(defgeneric * (x y)
  (:documentation "Multiply X and Y")
  (:method ((x number) (y number)) (cl:* x y))
  (:method ((x float) (y number)) (number-to-interval (cl:* x y)))
  (:method ((x number) (y float)) (number-to-interval (cl:* x y)))
  (:method ((x interval) (y number)) (* x (number-to-interval y)))
  (:method ((x number) (y interval)) (* (number-to-interval x) y))
  (:method ((x interval) (y interval))
    (if (or (interval-zerop x) (interval-zerop y))
        +zero-interval+
        (prog ((low (zero-bound))
               (high (zero-bound))
               (xl (low x))
               (xh (high x))
               (yl (low y))
               (yh (high y)))
           (declare (type interval-bound low high xl xh yl yh))
           (with-negative-rounding
               (setf low (cl:min (cl:* xl yl)
                                 (cl:* xl yh)
                                 (cl:* xh yl)
                                 (cl:* xh yh))))
           (with-positive-rounding
               (setf high (cl:max (cl:* xl yl)
                                  (cl:* xl yh)
                                  (cl:* xh yl)
                                  (cl:* xh yh))))
           (return (make-interval low high))))))

(defgeneric / (x y)
  (:documentation "Divide X by Y")
  (:method ((x number) (y number)) (cl:/ x y))
  (:method ((x float) (y number)) (number-to-interval (cl:/ x y)))
  (:method ((x number) (y float)) (number-to-interval (cl:/ x y)))
  (:method ((x interval) (y number)) (/ x (number-to-interval y)))
  (:method ((x number) (y interval)) (/ (number-to-interval x) y))
  (:method ((x interval) (y interval))
    (let ((yl (low y))
          (yh (high y)))
      (declare (type interval-bound yl yh))
      (cond ((or (cl:zerop yl)
                 (cl:zerop yh)
                 (cl:< yl 0 yh))
             (error 'division-by-zero))
            ((interval-zerop x) +zero-interval+)
            (t (prog ((low (zero-bound))
                      (high (zero-bound))
                      (xl (low x))
                      (xh (high x)))
                  (declare (type interval-bound low high xl xh))
                  (with-negative-rounding
                      (setf low (cl:min (cl:/ xl yl)
                                        (cl:/ xl yh)
                                        (cl:/ xh yl)
                                        (cl:/ xh yh))))
                  (with-positive-rounding
                      (setf high (cl:max (cl:/ xl yl)
                                         (cl:/ xl yh)
                                         (cl:/ xh yl)
                                         (cl:/ xh yh))))
                  (return (make-interval low high))))))))

(defgeneric = (x y)
  (:documentation "Is X equal to Y?")
  (:method ((x number) (y number)) (cl:= x y))
  (:method ((x interval) (y number))
    (cl:= (the interval-bound (low x)) (the interval-bound (high x)) y))
  (:method ((x number) (y interval))
    (cl:= x (the interval-bound (low y)) (the interval-bound (high y))))
  (:method ((x interval) (y interval))
    (and (cl:= (the interval-bound (low x)) (the interval-bound (low y)))
         (cl:= (the interval-bound (high x)) (the interval-bound (high y))))))

(defgeneric < (x y)
  (:documentation "Is X less than Y?")
  (:method ((x number) (y number)) (cl:< x y))
  (:method ((x interval) (y number)) (cl:< (the interval-bound (high x)) y))
  (:method ((x number) (y interval)) (cl:< x (the interval-bound (low y))))
  (:method ((x interval) (y interval))
    (cl:< (the interval-bound (high x)) (the interval-bound (low y)))))

(defgeneric <= (x y)
  (:documentation "Is X less than or equal to Y?")
  (:method ((x number) (y number)) (cl:<= x y))
  (:method ((x interval) (y number)) (cl:<= (the interval-bound (high x)) y))
  (:method ((x number) (y interval)) (cl:<= x (the interval-bound (low y))))
  (:method ((x interval) (y interval))
    (cl:<= (the interval-bound (high x)) (the interval-bound (low y)))))

(defgeneric > (x y)
  (:documentation "Is X greater than Y?")
  (:method ((x number) (y number)) (cl:> x y))
  (:method ((x interval) (y number)) (cl:> (the interval-bound (low x)) y))
  (:method ((x number) (y interval)) (cl:> x (the interval-bound (high y))))
  (:method ((x interval) (y interval))
    (cl:> (the interval-bound (low x)) (the interval-bound (high y)))))

(defgeneric >= (x y)
  (:documentation "Is X greater than or equal to Y?")
  (:method ((x number) (y number)) (cl:>= x y))
  (:method ((x interval) (y number)) (cl:>= (the interval-bound (low x)) y))
  (:method ((x number) (y interval)) (cl:>= x (the interval-bound (high y))))
  (:method ((x interval) (y interval))
    (cl:>= (the interval-bound (low x)) (the interval-bound (high y)))))


(defgeneric abs (x)
  (:documentation "Absolute value of X")
  (:method ((x number)) (cl:abs x))
  (:method ((x interval))
    (flet ((negate-interval (x)
             (make-interval (cl:- (the interval-bound (high x)))
                            (cl:- (the interval-bound (low x))))))
      (cond ((cl:plusp (the interval-bound (low x))) x)
            ((cl:minusp (the interval-bound (high x))) (negate-interval x))
            (t (make-interval (zero-bound)
                              (cl:max (cl:abs (the interval-bound (low x)))
                                      (cl:abs (the interval-bound (high x))))))
            ))))

(defgeneric sqrt (x)
  (:documentation "Square root of X")
  (:method ((x number)) (cl:sqrt x))
  (:method ((x interval))
    (let ((xl (low x))
          (xh (high x)))
      (declare (type interval-bound xl xh))
      (when (cl:minusp xh)
        (error 'arithmetic-error))
      ;; XXXX: The macros with-negative-rounding and with-positive-rounding
      ;; do not seem to change the behavior of cl:sqrt.  Otherwise, I'd use
      ;; them here.
      (make-interval (if (cl:plusp xl) (cl:sqrt xl) (zero-bound))
                     (cl:sqrt xh)))))

========================================
nasty.lisp
========================================

;; f(x,y) = 333.75 y^6 + x^2 (11 x^2 y^2 - y^6 - 121 y^4 - 2) +
;;          5.5 y^8 + x / (2 y).
 
;; for x = 77617 and y = 33096


(defun f (x y)
    (+ (* (/ 1335 4) (expt y 6))
     (* (expt x 2)
        (- (* 11 (expt x 2) (expt y 2))
           (expt y 6)
           (* 121 (expt y 4))
           2))
     (* (/ 11 2) (expt y 8))
     (/ x (* 2 y))))

;; Rump seems to have invented the polynomial evaluation example.

;; (defun rump (x y)
;;   (coerce (+ (* (/ 1335 4) (expt y 6))
;;              (* (expt x 2)
;;                 (- (* 11 (expt x 2) (expt y 2))
;;                    (expt y 6)
;;                    (* 121 (expt y 4))
;;                    2))
;;              (* (/ 11 2) (expt y 8))
;;              (/ x (* 2 y)))
;;           'double-float))



;; version with all operations made binary

(defun f1 (x y)
  (+ (+ (+ (* (/ 1335 4) (* y (* y (* y (* y (* y y))))))
           (* (* x x)
              (- (- (- (* 11 (* (* x x) (* y y)))
                       (* y (* y (* y (* y (* y y))))))
                    (* 121 (* y (* y (* y y)))))
                 2)))
        (* (/ 11 2) (* y (* y (* y (* y (* y (* y (* y y)))))))))
     (/ x (* 2 y))))


;; factor out common subexpressions in preparation for affine intervals

(defun f3 (x y)
  (let* ((x2 (* x x))
         (y2 (* y y))
         (y4 (* y2 y2))
         (y6 (* y2 y4))
         (y8 (* y4 y4)))
    (+ (+ (+ (* (/ 1335 4) y6)
             (* x2
                (- (- (- (* 11 (* x2 y2))
                         y6)
                      (* 121 y4))
                   2)))
          (* (/ 11 2) y8))
       (/ x (* 2 y)))))
From: ··········@YahooGroups.Com
Subject: Re: I'm not the only one who values interval-arithmetic
Date: 
Message-ID: <REM-2004jul16-001@Yahoo.Com>
> From: ······@speakeasy.net (Robert E. Brown)
> Date: 18 Apr 2004 23:24:49 -0400
Gee, I thought I responded to this long ago, but checking Google I see
I didn't post any followup, so here it is finally:

> This post is mostly for Robert Maas, who seems unreachable by email.

I'm reachable sometimes, but there's no guaranteed way to reach me.
Blame it on the spammers. If I post any e-mail address, it gets flooded
with so much spam I could easily miss a legitimate message in all the
mess, and mostly I don't even bother checking through the spam looking
for anything worth reading. On Yahoo! Mail, I get several thousand spam
per month, and not even one single legitimate e-mail in my inbox, so
why bother looking through the Bulk mail folder to see if there's any
non-spam there during a very unusual month? If I don't make an address
public, then maybe I won't get spam at that address, but how would you
know to use that address to contact me? If you know any free e-mail
service that works from lynx (no javascript, no https etc.) and blocks
incoming spam at the SMTP 5yz level and forwards all non-spam to an
address of my choosing, please let me know. Otherwise you can try
e-mailing to one of my spammed-to-death Yahoo! Mail addresses, namely
·······@Yahoo.Com, and see whether I ever notice your e-mail among the
spam.

Regarding your affine arithmetic:
> The package was written for SBCL

My ISP has only CMUCL here as far as I know.

> uses some non-standard features to change floating point rounding
> modes.

The key part is the low-level stuff, namely a clean representation of
bounds on a real number, and the low-level operations that take such
bounds as input and produce guaranteed bounds on the result. I've done
this sort of thing one way in CMUCL, but crudely using ANSI calls only
as far as I know, nothing optimized to use super fast CMUCL-specific
stuff. Of course anything using SBCL internals would be useless in
CMUCL, so I won't be able to compare your code to see if it's much
faster than straight ANSI code. In any case, I decided to do mine a
different way but haven't the energy to re-do it that new way, sigh.

> ;; Choose one of these as the type of interval upper and lower bounds.
> (deftype interval-bound () 'single-float)
> ;(deftype interval-bound () 'double-float)

It appears you allow only two levels of precision, and if double-float
isn't enough to do the job then your software just fails to produce a
usable result, right? In my version, there's no limit to the precision
except how much memory there is to store bignums. It would be nice to
have compatiblity between the two methodologies, allowing the
application to use whichever is best for the job.

> (defun number-to-interval (x)
>   (declare (type number x))
>   ;; XXXX: The conversion of x to interval bounds should be done twice,
>   ;; rounding down to create the lower bound and up to create the high
>   ;; bound.
>   (let ((bound (coerce x 'interval-bound)))
>     (make-interval bound bound)))

So loss of precision can occur when coercing a number to the kind of
number allowed as bounds of interval, and as a result one of the bounds
is not correct as the code is written above? Do you have an easy fix
for that, i.e. is it easy to coerce to interval-bound with bias one way
or the other to get each bound correct?

> (defgeneric + (x y)
> ...
>   (:method ((x float) (y number)) (number-to-interval (cl:+ x y)))
>   (:method ((x number) (y float)) (number-to-interval (cl:+ x y)))
> ...

That doesn't look right at all. Given one argument floating-point, you
use the inaccurate built-in floating-point arithmetic to generate a
number close to but not exactly equal to the correct answer, then you
claim the lower and upper bound are both that incorrect number,
resulting in one of the two bounds being wrong (except in the rare case
where built-in arithmetic gave exactly the correct result). Subtract
multiply etc. suffer from the same bug. You need to coerce the
arguments to interval first (with bugfix to that routine to bias bounds
appropriately), and then do interval arithmetic on the results.

> (defgeneric < (x y)
>   (:documentation "Is X less than Y?")
>   (:method ((x number) (y number)) (cl:< x y))
>   (:method ((x interval) (y number)) (cl:< (the interval-bound (high x)) y))
>   (:method ((x number) (y interval)) (cl:< x (the interval-bound (low y))))
>   (:method ((x interval) (y interval))
>     (cl:< (the interval-bound (high x)) (the interval-bound (low y)))))

So if the interval(s) are such that you can be sure x < y you return T,
which is correct, but if the interval(s) overlap so you can't know the
answer you return NIL even though the correct answer might be T?
That seems flaky. Maybe you should have a keyword argument of what to
return when in doubt, and hardwire T or NIL return only when you are
sure, else return that when-in-doubt value, which may be T or NIL for
some applications, or some other value in other applications?
To simplify the code, I would have accessors LOBND and UPBND which
operate on both intervals and numbers, returning just the number itself
(coerced to interval-bound with appropriate bias) when given a number,
and then the code for < can simply call the appropriate accessors
without needing to case-by-case deal with which argument is an
interval. Of course if you want to do non-interval arithmetic when none
of the arguments is an interval, then you'll need one case to handle
that specially.
From: Sashank Varma
Subject: Re: I'm not the only one who values interval-arithmetic
Date: 
Message-ID: <none-D7AC64.17025916072004@news.vanderbilt.edu>
In article <·················@Yahoo.Com>, ··········@YahooGroups.Com 
wrote:

> > From: ······@speakeasy.net (Robert E. Brown)
> > Date: 18 Apr 2004 23:24:49 -0400
> Gee, I thought I responded to this long ago, but checking Google I see
> I didn't post any followup, so here it is finally:
> 
> > This post is mostly for Robert Maas, who seems unreachable by email.
> 
> I'm reachable sometimes, but there's no guaranteed way to reach me.
> Blame it on the spammers. If I post any e-mail address, it gets flooded
> with so much spam I could easily miss a legitimate message in all the
> mess, and mostly I don't even bother checking through the spam looking
> for anything worth reading. On Yahoo! Mail, I get several thousand spam
> per month, and not even one single legitimate e-mail in my inbox, so
> why bother looking through the Bulk mail folder to see if there's any
> non-spam there during a very unusual month? If I don't make an address
> public, then maybe I won't get spam at that address, but how would you
> know to use that address to contact me? If you know any free e-mail
> service that works from lynx (no javascript, no https etc.) and blocks
> incoming spam at the SMTP 5yz level and forwards all non-spam to an
> address of my choosing, please let me know. Otherwise you can try
> e-mailing to one of my spammed-to-death Yahoo! Mail addresses, namely
> ·······@Yahoo.Com, and see whether I ever notice your e-mail among the
> spam.

Robert,

Please contact me regarding MCL 2.0.  I never heard back
from you.  You can reach me at:
     s a s h a n k  dot  v a r m a  at  v a n d e r b i l t  dot  e d u

Thanks.
From: Mark McConnell
Subject: Re: I'm not the only one who values interval-arithmetic
Date: 
Message-ID: <d3aed052.0407170610.3f376a3e@posting.google.com>
[This should be a reply to Maas's original post in this thread. 
Google groups won't let me reply to the top of the thread for some
reason.]

You mentioned the solution to Kepler's Conjecture.  (Does the densest
packing of spheres in three-dimensional space have to be the "obvious"
one attained by oranges in the grocery store?  Answer: yes.)  That
work was by Tom Hales.  He has published the details at
http://www.math.pitt.edu/~thales/kepler98/
In particular, he has posted his interval-arithmetic code, though it's
in C++.
From: Mario S. Mommer
Subject: Re: I'm not the only one who values interval-arithmetic
Date: 
Message-ID: <fzvfgkfljs.fsf@germany.igpm.rwth-aachen.de>
···············@yahoo.com (Mark McConnell) writes:
> You mentioned the solution to Kepler's Conjecture.  (Does the densest
> packing of spheres in three-dimensional space have to be the "obvious"
> one attained by oranges in the grocery store?  Answer: yes.)  That
> work was by Tom Hales.  He has published the details at
> http://www.math.pitt.edu/~thales/kepler98/
> In particular, he has posted his interval-arithmetic code, though it's
> in C++.

AFAICT, the proof is _not_ considered complete, since the programm has
still to be validated.
From: ··········@YahooGroups.Com
Subject: Re: Help on interval arithmetics package for lisp
Date: 
Message-ID: <REM-2004apr18-003@Yahoo.Com>
> From: ·····@karhu.Helsinki.FI (Krista Lagus)
> Date: 28 Jun 93 18:07:32
> I'd be grateful for pointers as to where I could find an
> interval-arithmetic package for lisp.

Nobody has responded to you yet. After all these years, is your
question still pending? By the way,I discovered your article just today
when doing a Google search. (Google didn't exist when you posted it!!)
From: Rahul Jain
Subject: Re: Help on interval arithmetics package for lisp
Date: 
Message-ID: <87k70cu0db.fsf@nyct.net>
··········@YahooGroups.Com writes:

> Nobody has responded to you yet. After all these years, is your
> question still pending? By the way,I discovered your article just today
> when doing a Google search. (Google didn't exist when you posted it!!)

The archive was called Deja News back then. :)

-- 
Rahul Jain
·····@nyct.net
Professional Software Developer, Amateur Quantum Mechanicist
From: Arnold Neumaier
Subject: Re: Help on interval arithmetics package for lisp
Date: 
Message-ID: <40896F37.2030104@univie.ac.at>
··········@YahooGroups.Com wrote:
>>From: ·····@karhu.Helsinki.FI (Krista Lagus)
>>Date: 28 Jun 93 18:07:32
>>I'd be grateful for pointers as to where I could find an
>>interval-arithmetic package for lisp.
> 
> 
> Nobody has responded to you yet. After all these years, is your
> question still pending? By the way,I discovered your article just today
> when doing a Google search. (Google didn't exist when you posted it!!)

Richard Fateman has an interval class for lisp for rational endpoints.
See:

http://www.cs.berkeley.edu/~fateman/mma1.6/intclass.lisp

interval arithmetic for Java is at
http://interval.sourceforge.net/interval/scheme/iaeval/README.html

Thanks to Janos Hajagos and David Wittenberg for providing this
information via the reliable computing mailing list:
   http://interval.louisiana.edu/mailing_list_form.html
For further questions about intervals, this a better forum than this
newsgroup.


Arnold Neumaier