From: Raymond Toy
Subject: Lisp history on declaration types?
Date: 
Message-ID: <4n90125koz.fsf@rtp.ericsson.se>
I was just curious how declarations for things like integer,
double-float and the bounds that can be used came to be.

My limited understanding is that most compilers don't really do
anything special if you say declare something as (double-float 1d0) or
(integer 0 1000).  If so, why was this added to the language?

I'm not complaining.  CMUCL can and does make good use of these
declarations.  Perhaps other compilers can too.

Curious,

Ray

From: Barry Margolin
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <CGjm4.10$mn5.363@burlma1-snr2>
In article <··············@rtp.ericsson.se>,
Raymond Toy  <···@rtp.ericsson.se> wrote:
>
>I was just curious how declarations for things like integer,
>double-float and the bounds that can be used came to be.
>
>My limited understanding is that most compilers don't really do
>anything special if you say declare something as (double-float 1d0) or
>(integer 0 1000).  If so, why was this added to the language?

For completeness, and to allow for arbitrary smartness by implementors.
Rather than the language designers trying to figure out just which
declarations would be useful and which wouldn't be, we let the user
describe their intent and then leave it to the implementor to work out the
optimizations.

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Raymond Toy
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4nn1phsxkr.fsf@rtp.ericsson.se>
>>>>> "Barry" == Barry Margolin <······@bbnplanet.com> writes:

    Barry> For completeness, and to allow for arbitrary smartness by implementors.
    Barry> Rather than the language designers trying to figure out just which
    Barry> declarations would be useful and which wouldn't be, we let the user
    Barry> describe their intent and then leave it to the implementor to work out the
    Barry> optimizations.

Thanks for the info, but I was kind of interested in the history as
well.  You know, something like, there weren't declarations in Tiny
Lisp 1, but some bright guy working on Proto-lisp said "This would be
cool to do".  The syntax looks like this.... Then Super Lisp Co. said,
"we can do even better if we had such and such declarations and we'll
use this syntax because it's nicer."

I find such things quite interesting because nothing ever comes forth
in full form.  Kind of like Kepler's (?) description of how he arrived
at his laws.  I think he made several mistakes on the way, but they
all cancelled out in the end so that his laws were right.

Ray
From: Fred Gilham
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <u7wvoku3l4.fsf@snapdragon.csl.sri.com>
>Thanks for the info, but I was kind of interested in the history as
>well.  You know, something like, there weren't declarations in Tiny
>Lisp 1, but some bright guy working on Proto-lisp said "This would be
>cool to do".

JonL White, in his talk at the 1999 Lisp User Group conference, says
the following in the section entitled Fast Arithmetic and Ncomplr:

     Somewhere around 1971, the author noticed a visitor at the MIT AI
     Lab (on leave from a technical laboratory in Tokyo for one year)
     typing in some Lisp code that appeared for all intents and
     purposes to be a transliteration of a Fortran program.  When
     asked, Yoshio Shirai indeed confirmed that he was coding
     exclusively in Fortran because upon his return to Japan, there
     would be no Lisp system available.  Fortran would not be the
     first choice, given that so much of his algorithms would be
     ``AI-like''; on the other hand, the poor performance of numerical
     code written in Lisp was a concern only to the degree that the
     numerical component was overly noticeable in time cost.

     That confrontation (writing Fortran in Lisp), along with the twin
     pressures of better numerics in Lisp for computer vision
     processing, and for better performance in symbolic algebra
     systems when such had to fall back to some real number crunching,
     led the author to question whether lexiccally-discernable numeric
     expressions in Lisp could be compiled exactly like such
     expressions would be by a conventional Fortran compiler.

     Step one was to convert the numeric representations to a uniform
     format, such as is the case in the Fortran world (see the
     discussion on the emergence of the Bibop pointer encoding scheme
     for PDP10 MacLisp, in Section 2, under the heading ``Entering the
     MacLisp Era'').  Step two was making some additions to the
     language (with attendant effects on the Lisp compiler) to add an
     optional static typing feature to the language, namely Declare.
     Thus the PDP10 MacLisp compiler would have some CHANCE of being
     able to detect numeric expressions at compile time, as being of
     type Fix or Float, and emit the more numerically efficient code
     sequences.

-- 
Fred Gilham                                      ······@csl.sri.com
I have over the years been viewed as a man of the left and a man of
the right, and the truth is that I've never put much stake in such
labels. But this I have learned: the left patrols its borders and
checks membership credentials ever so much more scrupulously, even
ruthlessly, than does the right.            -- Richard John Neuhaus
From: Duane Rettig
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4ya926s6h.fsf@beta.franz.com>
Raymond Toy <···@rtp.ericsson.se> writes:

> I was just curious how declarations for things like integer,
> double-float and the bounds that can be used came to be.
> 
> My limited understanding is that most compilers don't really do
> anything special if you say declare something as (double-float 1d0) or
> (integer 0 1000).  If so, why was this added to the language?

These declarations are extremely useful, especially for type
propagation and code generation.  It also keeps the fixnum/bignum
crossover from becoming anything other than an implementation
choice, especially if the compiler normalizes a
(declare (type fixnum ...)) form into e.g.
(declare (type (integer -536870912 536870911))).

> I'm not complaining.  CMUCL can and does make good use of these
> declarations.  Perhaps other compilers can too.

CMUCL is not the only one:

Allegro CL Enterprise Edition 5.0.1 [SPARC] (9/22/99 9:54)
Copyright (C) 1985-1999, Franz Inc., Berkeley, CA, USA.  All Rights Reserved.
;; Optimization settings: safety 1, space 1, speed 1, debug 2.
;; For a complete description of all compiler switches given the current
;; optimization settings evaluate (EXPLAIN-COMPILER-SETTINGS).
USER(1): (defun slow-sqrt (x)
             (declare (optimize speed (safety 0) (debug 0)) (type double-float x))
             (sqrt x))
SLOW-SQRT
USER(2): (disassemble *)
;; disassembly of #<Function (:ANONYMOUS-LAMBDA 3) @ #x44e3b82>
;; formals: X
;; constant vector:
0:	SQRT

;; code start: #x44e3b44:
   0: 9de3bf98     save	%o6, #x-68, %o6
   4: fd1e2006     ldd	[%i0 + 6], %f30
   8: de012213     ld	[%g4 + 531], %o7	; SYS::NEW-DOUBLE-FLOAT
  12: 9fc3e000     jmpl	%o7 + 0, %o7
  16: 86182000     xor	%g0, #x0, %g3
  20: c4076022     ld	[%i5 + 34], %g2 	; SQRT
  24: b0100008     mov	%o0, %i0
  28: 81e80000     restore	%g0, %g0, %g0
  32: 81c1200b     jmp	%g4 + 11
  36: 86182001     xor	%g0, #x1, %g3
USER(3): (defun fast-sqrt (x)
             (declare (optimize speed (safety 0) (debug 0)) (type (double-float 0.0d0) x))
             (sqrt x))
FAST-SQRT
USER(4): (disassemble *)
;; disassembly of #<Function (:ANONYMOUS-LAMBDA 4) @ #x44f0c6a>
;; formals: X

;; code start: #x44f0c44:
   0: fd1a2006     ldd	[%o0 + 6], %f30
   4: bda0055e     fsqrtd	%f30, %f30
   8: c4012213     ld	[%g4 + 531], %g2	; SYS::NEW-DOUBLE-FLOAT
  12: 81c0a000     jmp	%g2 + 0
  16: 86182000     xor	%g0, #x0, %g3
USER(5): 

-- 
Duane Rettig          Franz Inc.            http://www.franz.com/ (www)
1995 University Ave Suite 275  Berkeley, CA 94704
Phone: (510) 548-3600; FAX: (510) 548-8253   ·····@Franz.COM (internet)
From: Raymond Toy
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4nsnz9sz5q.fsf@rtp.ericsson.se>
>>>>> "Duane" == Duane Rettig <·····@franz.com> writes:

    Duane> Raymond Toy <···@rtp.ericsson.se> writes:
    >> I was just curious how declarations for things like integer,
    >> double-float and the bounds that can be used came to be.
    >> 
    >> My limited understanding is that most compilers don't really do
    >> anything special if you say declare something as (double-float 1d0) or
    >> (integer 0 1000).  If so, why was this added to the language?

    Duane> These declarations are extremely useful, especially for type
    Duane> propagation and code generation.  It also keeps the fixnum/bignum
    Duane> crossover from becoming anything other than an implementation
    Duane> choice, especially if the compiler normalizes a
    Duane> (declare (type fixnum ...)) form into e.g.
    Duane> (declare (type (integer -536870912 536870911))).

Isn't the fixnum/bignum crossover an implementation choice?  Or do you
mean the user can specify precisely what he wants and let the
implementation handle that has best it can?

    >> I'm not complaining.  CMUCL can and does make good use of these
    >> declarations.  Perhaps other compilers can too.

    Duane> CMUCL is not the only one:

I did not mean to disparage others implementation; I just didn't know
for sure.  My personal copy of ACL wasn't handy so I couldn't test it
there.  I knew ACL could use declarations, I just wasn't sure how
much.  (You may recall you helped me out several years ago on getting
faster FP performance from ACL.  It was a simple Gaussian random
number generator.)

Just out of curiosity, what does ACL do with this:

(defun tst (x)
  (declare (type (double-float (0d0) (1d0)) x)
           (optimize (speed 3) (safety 0)))
  (sqrt (* x (- 1 x))))

CMUCL says

      58:       ADD   -18, %CODE
      5C:       ADD   %CFP, 32, %CSP

      60:       LDDF  [%A0+1], %F0           ; %A0 = #:G1
      64:       LD    [%CODE+13], %A0        ; No-arg-parsing entry point
      68:       LDDF  [%A0+1], %F2
      6C:       FSUBD %F2, %F0, %F2
      70:       FMULD %F0, %F2, %F0
      74:       FSQRTD %F0, %F0

(Boxing of double-float result deleted.)

Ray
From: Hidayet Tunc Simsek
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <389A0AEA.77BF000@EECS.Berkeley.Edu>
While we're on the topic, I have a question:

Is it possible to avoid boxing with a (declaim (ftype ... declaration?

e.g.
----
(declaim (ftype (function (double-float) double-float)
                foo))
 
(defun foo (x)
  (declare (type double-float x))
  (* -1.0d0 x))
 

* (time (foo 1.0d0))
Compiling LAMBDA NIL: 
Compiling Top-Level Form: 
 
Evaluation took:
  0.0 seconds of real time
  0.0 seconds of user run time
  0.0 seconds of system run time
  0 page faults and
  64 bytes consed.
-1.0d0

Apparently not, why does boxing a single double-float cons so many
bytes??

Thanks,
Tunc

Raymond Toy wrote:
> 
> >>>>> "Duane" == Duane Rettig <·····@franz.com> writes:
> 
>     Duane> Raymond Toy <···@rtp.ericsson.se> writes:
>     >> I was just curious how declarations for things like integer,
>     >> double-float and the bounds that can be used came to be.
>     >>
>     >> My limited understanding is that most compilers don't really do
>     >> anything special if you say declare something as (double-float 1d0) or
>     >> (integer 0 1000).  If so, why was this added to the language?
> 
>     Duane> These declarations are extremely useful, especially for type
>     Duane> propagation and code generation.  It also keeps the fixnum/bignum
>     Duane> crossover from becoming anything other than an implementation
>     Duane> choice, especially if the compiler normalizes a
>     Duane> (declare (type fixnum ...)) form into e.g.
>     Duane> (declare (type (integer -536870912 536870911))).
> 
> Isn't the fixnum/bignum crossover an implementation choice?  Or do you
> mean the user can specify precisely what he wants and let the
> implementation handle that has best it can?
> 
>     >> I'm not complaining.  CMUCL can and does make good use of these
>     >> declarations.  Perhaps other compilers can too.
> 
>     Duane> CMUCL is not the only one:
> 
> I did not mean to disparage others implementation; I just didn't know
> for sure.  My personal copy of ACL wasn't handy so I couldn't test it
> there.  I knew ACL could use declarations, I just wasn't sure how
> much.  (You may recall you helped me out several years ago on getting
> faster FP performance from ACL.  It was a simple Gaussian random
> number generator.)
> 
> Just out of curiosity, what does ACL do with this:
> 
> (defun tst (x)
>   (declare (type (double-float (0d0) (1d0)) x)
>            (optimize (speed 3) (safety 0)))
>   (sqrt (* x (- 1 x))))
> 
> CMUCL says
> 
>       58:       ADD   -18, %CODE
>       5C:       ADD   %CFP, 32, %CSP
> 
>       60:       LDDF  [%A0+1], %F0           ; %A0 = #:G1
>       64:       LD    [%CODE+13], %A0        ; No-arg-parsing entry point
>       68:       LDDF  [%A0+1], %F2
>       6C:       FSUBD %F2, %F0, %F2
>       70:       FMULD %F0, %F2, %F0
>       74:       FSQRTD %F0, %F0
> 
> (Boxing of double-float result deleted.)
> 
> Ray
From: Barry Margolin
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <Gspm4.45$mn5.455@burlma1-snr2>
In article <················@EECS.Berkeley.Edu>,
Hidayet Tunc Simsek  <······@EECS.Berkeley.Edu> wrote:
>While we're on the topic, I have a question:
>
>Is it possible to avoid boxing with a (declaim (ftype ... declaration?

Probably not.  The function might be called from a context where the
declaration wasn't in effect, or it might be called through FUNCALL or
APPLY, so the callee wouldn't know that it's returning an unboxed number.

It would be conceivable for a function to have different entrypoints or
implicit parameters depending on whether the callee knows its declaration
or not (I've suggested the same thing be done for processing keyword
arguments at compile time), but AFAIK no implementation does this.

You may be able to achieve it by using INLINE, though.

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Tunc Simsek
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <Pine.SOL.4.10.10002031848280.680-100000@tudor.EECS.Berkeley.EDU>
o.k., I see why the compiler has to box the result.
I tried to do manual boxing but the function GOO still
conses 48 bytes??  Am I missing something?  The code below 
is exactly what I have in foo.lisp which I am compiling from CMUCL:

(defvar *s* (make-array 1 :element-type 'double-float))
(declaim (type (simple-array double-float (1)) *s*))

(defun foo (x)
  (declare (type double-float x)
           (type (simple-array double-float (1)) *s*)
           (optimize (speed 3) (safety 0) (space 0) (compilation-speed
0)))
     (setf (aref *s* 0) (* -1.0d0 x))
     )

(defun boo (x)
  (declare (type double-float x)
           (type (simple-array double-float (1)) *s*)
           (optimize (speed 3) (safety 0) (space 0) (compilation-speed
0)))
     (setf (aref *s* 0) (* -1.0d0 x))
     *s*)


Thanks,
Tunc

On Fri, 4 Feb 2000, Barry Margolin wrote:

> In article <················@EECS.Berkeley.Edu>,
> Hidayet Tunc Simsek  <······@EECS.Berkeley.Edu> wrote:
> >While we're on the topic, I have a question:
> >
> >Is it possible to avoid boxing with a (declaim (ftype ... declaration?
> 
> Probably not.  The function might be called from a context where the
> declaration wasn't in effect, or it might be called through FUNCALL or
> APPLY, so the callee wouldn't know that it's returning an unboxed number.
> 
> It would be conceivable for a function to have different entrypoints or
> implicit parameters depending on whether the callee knows its declaration
> or not (I've suggested the same thing be done for processing keyword
> arguments at compile time), but AFAIK no implementation does this.
> 
> You may be able to achieve it by using INLINE, though.
> 
> -- 
> Barry Margolin, ······@bbnplanet.com
> GTE Internetworking, Powered by BBN, Burlington, MA
> *** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
> Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
> 
> 
From: Raymond Toy
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4nemassya1.fsf@rtp.ericsson.se>
>>>>> "Tunc" == Tunc Simsek <······@tudor.EECS.Berkeley.EDU> writes:

    Tunc> o.k., I see why the compiler has to box the result.
    Tunc> I tried to do manual boxing but the function GOO still
    Tunc> conses 48 bytes??  Am I missing something?  The code below 

I think BOO (not GOO?) consing 48 bytes is consistent with my previous
message.  It's 16 bytes less because you don't box up a double-float
result but instead return the array, which is already boxed.  So it's
16-bytes for X and another 32 for time.

Ray
From: Hidayet Tunc Simsek
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <389B10CD.FB59044B@EECS.Berkeley.Edu>
more experimentation shows that it 48 for time and 0 for x, which is
also consistent.

Tunc

Raymond Toy wrote:
> 
> >>>>> "Tunc" == Tunc Simsek <······@tudor.EECS.Berkeley.EDU> writes:
> 
>     Tunc> o.k., I see why the compiler has to box the result.
>     Tunc> I tried to do manual boxing but the function GOO still
>     Tunc> conses 48 bytes??  Am I missing something?  The code below
> 
> I think BOO (not GOO?) consing 48 bytes is consistent with my previous
> message.  It's 16 bytes less because you don't box up a double-float
> result but instead return the array, which is already boxed.  So it's
> 16-bytes for X and another 32 for time.
> 
> Ray
From: Raymond Toy
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4nhffprn3t.fsf@rtp.ericsson.se>
>>>>> "Hidayet" == Hidayet Tunc Simsek <······@EECS.Berkeley.Edu> writes:

    Hidayet> While we're on the topic, I have a question:
    Hidayet> Is it possible to avoid boxing with a (declaim (ftype ... declaration?

    Hidayet> e.g.
    Hidayet> ----
    Hidayet> (declaim (ftype (function (double-float) double-float)
    Hidayet>                 foo))
 
    Hidayet> (defun foo (x)
    Hidayet>   (declare (type double-float x))
    Hidayet>   (* -1.0d0 x))
 

    Hidayet> * (time (foo 1.0d0))
    Hidayet> Compiling LAMBDA NIL: 
    Hidayet> Compiling Top-Level Form: 
 
    Hidayet> Evaluation took:
    Hidayet>   0.0 seconds of real time
    Hidayet>   0.0 seconds of user run time
    Hidayet>   0.0 seconds of system run time
    Hidayet>   0 page faults and
    Hidayet>   64 bytes consed.
    Hidayet> -1.0d0

    Hidayet> Apparently not, why does boxing a single double-float cons so many
    Hidayet> bytes??

I'm guessing here, but on CMUCL a boxed float consists of a header, a
filler, and the value itself.  (The filler is used to align the value
on a double-float boundary.)  That's 16 bytes.  You need to box up
1.0d0 and box up the result, so that's 32 bytes.  I guess the rest
comes from time?

Ray
From: Robert Monfera
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <3899CD8B.F559656F@fisec.com>
Raymond Toy wrote:

> I was just curious how declarations for things like integer,
> double-float and the bounds that can be used came to be.

Yes, its history must be interesting (e.g., when type declarations were
first used).

> My limited understanding is that most compilers don't really do
> anything special if you say declare something as (double-float 1d0)
> or (integer 0 1000).

Commercial compilers I know and CMUCL make heavy use of type
declarations.  If the compiler can rely on certain values being of a
certain type, it can compile code that does no type checking, you may
avoid boxing (e.g., in declared arrays) and use hardware operations
directly.  This not only reduces or eliminates type checks, but also
helps avoid function calls by in-lining very short pieces of code for
built-in operations.

In my experience, good declarations make a ~10-100x speedup of tight,
number-crunching loops - unless the undeclared version conses so much
that it will die of paging (i.e., infinite speedup with declarations :-)

A trivial example is

(typecase (the fixnum baz)
     (fixnum (foo ...))
     (bignum (bar ...)))

which gets speed-optimized to

(foo ...) in LispWorks.

There have been some benchmarks and code posted recently that should
give a sense of speed-up: use dejanews with keyword "declare" :-)

> CMUCL can and does make good use of these
> declarations.  Perhaps other compilers can too.

Yes, though CMUCL is known to have a very good type inference mechanism
already - declarations are probably _less_ important for CMUCL as for
ACL or LispWorks.

Declarations tend to make a huge difference if there are underlying
hardware instructions: while my laptop can add 64MB of FPU-supported
double-floats in 0.4s on ACL, adding the same number (8m) of fixnums
will cons ~200MB if the accumulator overflows and becomes a (not
hardware-optimized) bignum.

Type declarations are usually upgraded (see for example
UPGRADED-ARRAY-ELEMENT-TYPE), so (INTEGER 0 1000) becomes (UNSIGNED-BYTE
16) on ACL and LispWorks.

Declarations have their price (extra development time, maybe restricted
input data) and specific results are quite implementation-dependent, but
it pays off big time in speed-critical parts of the program.

Several big guns gave insightful thoughts on-line (Erik, Kent, Tim,
Pierre, Duane, Barry, Pekka, Bulent,...) and off-line (Graham, ...).

Regards
Robert
From: Raymond Toy
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4npuudsxv9.fsf@rtp.ericsson.se>
>>>>> "Robert" == Robert Monfera <·······@fisec.com> writes:

    Robert> Yes, though CMUCL is known to have a very good type inference mechanism
    Robert> already - declarations are probably _less_ important for CMUCL as for
    Robert> ACL or LispWorks.

I would say yes and no.  CMUCL's good type inference means I don't
have to have as many declarations, but having good declarations can
help CMUCL a lot too.  Like my example on sqrt(x*(1-x)).  If you KNOW
0 < x < 1, and say so, then CMUCL can do a very good job.

Ray
From: Kent M Pitman
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <sfw3dr83cp7.fsf@world.std.com>
Raymond Toy <···@rtp.ericsson.se> writes:

> I was just curious how declarations for things like integer,
> double-float and the bounds that can be used came to be.
> 
> My limited understanding is that most compilers don't really do
> anything special if you say declare something as (double-float 1d0) or
> (integer 0 1000).  If so, why was this added to the language?

So that cool compilers could come along later without us having to revise
the language to allow them to conform and win.  It's well-known that having
type information can improve compilation, and it's also well-known that
Lisp doesn't require such information.  But we didn't want the lack of
such information being required to keep users from providing it, nor did 
we want the lack of a way for users to say it to be the only thing holding
back vendors from doing something better over time.

Lisp speaks not only to the present but to the future.  Doing a universal
quantification over "most compilers" neglects the inability to know what
will come.

I often speak of "portability" as being not only cross-platform to 
different vendors, but also cross-platform to the same vendor at later
points in time, which can sometimes be as big a deal.

> I'm not complaining.  CMUCL can and does make good use of these
> declarations.  Perhaps other compilers can too.

CMU CL didn't exist when these features were implemented.  The work in 
CMU CL was partly to test whether these features CL had were in fact useful
in the way they purported to be.  (I think the answer they came to was
yes.)  Whether they get added to any particular vendor's lisp is an economic
consideration, not a technical one.

Put another way, having the declarations in the language allows you to
submit succinct bug reports to vendors with one or two line programs that
you wrote and a statement of your efficiency expectations; the fact that 
you're using standardized mechanisms of expressions increases the likelihood
that the vendor will believe someone else will have an equivalent need.
If you submitted special-purpose syntax, in all probability no on else will
ever ask for the same thing as you, and vendors will probably be less likely
to go out on a limb and make one-off syntax just for your purpose, and so 
the likelihood you'll ever see forward progress is reduced.

At least, that's my opinion about why we did it.  Others' opinions might
legitimately vary.
From: Jeff Dalton
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <x2g0v28fxz.fsf@todday.aiai.ed.ac.uk>
Raymond Toy <···@rtp.ericsson.se> writes:

> I was just curious how declarations for things like integer,
> double-float and the bounds that can be used came to be.
> 
> My limited understanding is that most compilers don't really do
> anything special if you say declare something as (double-float 1d0) or
> (integer 0 1000).  If so, why was this added to the language?

I don't know about range declarations such as (integer 0 1000),
but quite a few implementations pay attention to fixnum, double-float,
and the like.
From: Robert Monfera
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <38A1C2F0.E3BED065@fisec.com>
Jeff Dalton wrote:

> I don't know about range declarations such as (integer 0 1000),
> but quite a few implementations pay attention to fixnum,
>double-float, and the like.

(integer most-negative-fixnum most-positive-fixnum) is the same as
fixnum, as an example.  (integer -100000 100000), as well as fixnum will
be mapped to a fixnum or (unsigned-byte 32) representation.

Robert
From: Raymond Toy
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4nr9emm870.fsf@rtp.ericsson.se>
>>>>> "Robert" == Robert Monfera <·······@fisec.com> writes:

    Robert> Jeff Dalton wrote:

    >> I don't know about range declarations such as (integer 0 1000),
    >> but quite a few implementations pay attention to fixnum,
    >> double-float, and the like.

    Robert> (integer most-negative-fixnum most-positive-fixnum) is the same as
    Robert> fixnum, as an example.  (integer -100000 100000), as well as fixnum will
    Robert> be mapped to a fixnum or (unsigned-byte 32) representation.

How does that work?  A fixnum is not an (unsigned-byte 32).  Did you
mean (signed-byte 32)?

Ray
 
From: Robert Monfera
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <38A1D4FF.EF01FEF8@fisec.com>
Raymond Toy wrote:

> How does that work?  A fixnum is not an (unsigned-byte 32).  Did you
> mean (signed-byte 32)?

Yes, of course.  Indeed, sometimes I use (signed-byte 32) even if it is
known that the number will never be negative, because using (signed-byte
32) is sometimes faster than (unsigned-byte 32).

Robert
From: Raymond Toy
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <4nhffim1fh.fsf@rtp.ericsson.se>
>>>>> "Robert" == Robert Monfera <·······@fisec.com> writes:

    Robert> Raymond Toy wrote:

    >> How does that work?  A fixnum is not an (unsigned-byte 32).  Did you
    >> mean (signed-byte 32)?

    Robert> Yes, of course.  Indeed, sometimes I use (signed-byte 32)
    Robert> even if it is known that the number will never be
    Robert> negative, because using (signed-byte
    Robert> 32) is sometimes faster than (unsigned-byte 32).

Why is that?  What makes unsigned faster than signed in your
situation?

Just curious,

Ray
From: Jeff Dalton
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <x2puu56jyg.fsf@todday.aiai.ed.ac.uk>
Robert Monfera <·······@fisec.com> writes:

> Jeff Dalton wrote:
> 
> > I don't know about range declarations such as (integer 0 1000),
> > but quite a few implementations pay attention to fixnum,
> >double-float, and the like.
> 
> (integer most-negative-fixnum most-positive-fixnum) is the same as
> fixnum, as an example.  (integer -100000 100000), as well as fixnum will
> be mapped to a fixnum or (unsigned-byte 32) representation.

I'm not at all sure that (integer most-negative-fixnum most-positive-fixnum)
will in fact be treated as the same as fixnum by all implementations.
Some may not map range types to "atomic" types at all.

Anyway, an interesting thing about GCL that I forgot to mention is
that integer has the effect of getting you some integer-specific
(but including bignums) arithmetic.

It's pretty easy to see the effects of declarations in KCL/AKCL/GCL
because the emitted code is C and because some of the mappings are
on the plists of the function-name symbols.  For example:

GCL (GNU Common Lisp)  Version(2.3) Wed Dec 15 16:51:03 GMT 1999
Licensed under GNU Library General Public License
Contains Enhancements by W. Schelter

>(symbol-plist '+)

(COMPILER::INLINE-ALWAYS
    (((FIXNUM FIXNUM) FIXNUM 0 "(#0)+(#1)")
     ((INTEGER INTEGER INTEGER) INTEGER 24 "addii(#0,addii(#1,#2))")
     ((INTEGER INTEGER) INTEGER 24 "addii(#0,#1)")
     ((SHORT-FLOAT SHORT-FLOAT) SHORT-FLOAT 8 "(#0)+(#1)")
     ((LONG-FLOAT LONG-FLOAT) LONG-FLOAT 8 "(double)(#0)+(double)(#1)")
     ((COMPILER::FIXNUM-FLOAT COMPILER::FIXNUM-FLOAT) LONG-FLOAT 0
      "(double)(#0)+(double)(#1)")
     ((COMPILER::FIXNUM-FLOAT COMPILER::FIXNUM-FLOAT) SHORT-FLOAT 0
      "(double)(#0)+(double)(#1)")
     ((T T) T 1 "number_plus(#0,#1)"))
    COMPILER::RETURN-TYPE T COMPILER::ARG-TYPES (*) COMPILER::LFUN
    "Lplus")

-- jeff
From: Robert Monfera
Subject: Re: Lisp history on declaration types?
Date: 
Message-ID: <38A2FC56.9FEB738@fisec.com>
Jeff Dalton wrote:

> Anyway, an interesting thing about GCL that I forgot to mention is
> that integer has the effect of getting you some integer-specific
> (but including bignums) arithmetic.

This sounds very useful.  How does it work?  A tag bit specifies if the
number is a fixnum or bignum?  Is that tagging more specific than in the
general case in that it requires fewer bits?  (Not important to me -
that would just potentially enable bigger fixnums.)  Can bignum
operations get away without consing with this representation in GCL
(e.g., accumulating values in a big vector that is mostly fixnum with
some bignums, and the accumulated value is likely to become a bignum)?

Once I thought it's straightforward to do a representation like that at
the user level (using signed-byte 32 with the MSB maintained as an
overflow indicator and type tag), but implementations don't support some
ANSI features of COMPILER-MACROs, e.g., when the function name is a list
like (SETF VREF), making it more cumbersome to allow the use of
accessors and customized operations without having to worry about how
numbers are represented, and only LispWorks seems to reduce

(typecase (the fixnum a)
	(fixnum (foo a))
	(double-float (bar a)))
to
(foo a)

What does "addii" do in GCL?  Is it a C function that may get inlined?

Thanks,
Robert