[comp.lang.lisp] Summing a list

rogers@eagle.SRC.Honeywell.COM (Brynn Rogers) (10/25/88)

 I Have a silly question.   I need to take the sum of a list 
 of numbers.
 (SETQ NUMLIST '(1 2 3 6 7))
 This is quite simple, really, but what is the BEST way to do it?
 I like: 
 
 (EVAL (CONS '+ NUMLIST))

 But someone else says this would be faster::
  
 (LET ((SUM 0))
    (DOLIST (NUM NUMLIST)
       (SETQ SUM (+ SUM NUM))))  ;; or maybe (INCF SUM NUM)


of course, there is always:

(DEFUN SUM (NUMLIST)
   (COND ((NULL NUMLIST) 0)
         (T (+ (FIRST NUMLIST) (SUM (CDR NUMLIST))))))

    I think it's obvious that the last would be slow.
    Also it's Obvious that there are Many ways to do this.
What is the BEST (for speed and/or elegance) way to sum a list??

(I Run Gold Hills Common 3.0 on a Compaq 386/20 with a 387)

Thanks,    Brynn Rogers   rogers@src.honeywell.com

rogers@orion.SRC.Honeywell.COM (Brynn Rogers) (10/26/88)

Answering half of my own question.
(EVAL (CONS '+ NUMLIST)) 
is 700 times faster than summing useing a DOLIST.

BUT this was EVALed code.
In compiled code the DOLIST was about 15% faster than 
(EVAL (CONS '+ NUMLIST)) which (no surprise here) wasn't any faster
			 compiled as apposed to evaled.
Is there a better way?? (I think there has got to be)

Brynn Rogers      rogers@src.honeywell.com
P.S. I apoligize for being a novice poster.  But I have to learn somtime :-)

raymond@pioneer.arc.nasa.gov.arpa (Eric A. Raymond) (10/26/88)

In article <10794@srcsip.UUCP> rogers@eagle.UUCP (Brynn Rogers) writes:
>
> I Have a silly question.   I need to take the sum of a list 
> of numbers.
> (SETQ NUMLIST '(1 2 3 6 7))
> This is quite simple, really, but what is the BEST way to do it?
> I like: 
> 
> (EVAL (CONS '+ NUMLIST))

Ugggggh!  It may seem novel but its a poor, outdated style of programming.
First you waste a cons cell, make your code very obscure, and force the code
to be interpreted.

> But someone else says this would be faster::
>  
> (LET ((SUM 0))
>    (DOLIST (NUM NUMLIST)
>       (SETQ SUM (+ SUM NUM))))  ;; or maybe (INCF SUM NUM)

Or any other itertive control structure

>
>
>of course, there is always:
>
>(DEFUN SUM (NUMLIST)
>   (COND ((NULL NUMLIST) 0)
>         (T (+ (FIRST NUMLIST) (SUM (CDR NUMLIST))))))
>
>    I think it's obvious that the last would be slow.

Not necessarily.

How about :

  (apply #'+ NUMLIST)

  or

  (reduce #'+ NUMLIST)


Name: Eric A. Raymond
ARPA: raymond@pioneer.arc.nasa.gov
SLOW: NASA Ames Research Center, MS 244-17, Moffett Field, CA 94035

Nothing left to do but :-) :-) :-)

gandalf@csli.STANFORD.EDU (Juergen Wagner) (10/26/88)

How about
	-> (reduce #'+ '(1 2 3 4 5 6 7 8 9 10))
	55

This will allow the compiler to make any optimizations suitable for the machine
you are running on, and it allows you to avoid thinking about the "most 
efficient way" of representing this.

-- 
Juergen "Gandalf" Wagner,		   gandalf@csli.stanford.edu
Center for the Study of Language and Information (CSLI), Stanford CA

andreasg@boulder.Colorado.EDU (Andreas Girgensohn) (10/26/88)

A better way is the following form because eval invokes the
interpreter and produces a lot of garbage.  The dolist example should
be much faster in compiled code.

  (apply '+ numlist)

The difference is that apply doesn't evaluate the elements of the list
whereas eval does it.  It's no difference is this case because numbers
(the elements of the list) are evaluate to themselves.  

Andreas Girgensohn
andreasg@boulder.colorado.edu

barmar@think.COM (Barry Margolin) (10/26/88)

I decided to time all the various methods that have been discussed.  I
tried them on a Symbolics 3640 running Genera 7.2 and a Sun 3/280
running Lucid CL 2.0.3.  I used the default OPTIMIZE parameters.

Here is the function I used for the tests:

(defun sum-test (list &optional (count 100))
  (macrolet ((repeat (&body body) `(dotimes (i count) do (progn .,body)))
	     (time-it (form) `(#+symbolics without-interrupts
			       #-symbolics progn
			       (time ,form))))
    (flet ((my-false (&rest x)
	     (declare (ignore x))
	     nil))
      (flet ((nothing () (repeat (my-false list)))
	     (do-loop () (repeat (let ((sum 0)) (dolist (item list) (incf sum item)) sum)))
	     (recursive ()
	       (labels ((recursive-call (list)
			  (if (null list) 0
			      (+ (car list) (recursive-call (cdr list))))))
		 (repeat (recursive-call list))))
	     (eval-+ () (repeat (eval (cons '+ list))))
	     (apply-+ () (repeat (apply #'+ list)))
	     (reduce-+ () (repeat (reduce #'+ list))))
	(time-it (nothing))
	(time-it (eval-+))
	(time-it (do-loop))
	(time-it (recursive))
	(time-it (apply-+))
	(time-it (reduce-+))))))

The argument I gave was a list of the integers from 1 to 1000.

NOTHING is there just as a control, to show the function call
overhead.  This overhead turned out to be negligible on both systems.

On the Symbolics the fastest method was APPLY-+, followed closely by
DO-LOOP.  REDUCE-+ and RECURSIVE took five and six times as long as
APPLY-+, respectively, and EVAL-+ took more than twice as long as
RECURSIVE, and consed a great deal.

In Lucid the fastest method was DO-LOOP.  RECURSIVE took a little less
than twice as long, APPLY-+ took over 8 times as long, and REDUCE-+
took twice as long as APPLY-+.  EVAL-+ was between APPLY-+ and
REDUCE-+.  GCs took place during EVAL-+ and REDUCE-+ all the times I
tried, so the GC time is being factored into these results.  The times
I am comparing are the "User cpu time".

So, if these two are representative implementations, and performance
is an issue, the best way to sum a list is to write your own loop.  In
my opinion, the clearest version is the one using APPLY, or perhaps
the one using REDUCE (APPLY has been around much longer, so I'm
generally more comfortable with it).

Barry Margolin
Thinking Machines Corp.

barmar@think.com
{uunet,harvard}!think!barmar

rcp@perseus. (Rob Pettengill) (10/27/88)

In article <10794@srcsip.UUCP> rogers@eagle.UUCP (Brynn Rogers) writes:
;
; I Have a silly question.   I need to take the sum of a list 
; of numbers.
; (SETQ NUMLIST '(1 2 3 6 7))
; This is quite simple, really, but what is the BEST way to do it?
; I like: 
; 
; (EVAL (CONS '+ NUMLIST))
;
; But someone else says this would be faster::
;  
; (LET ((SUM 0))
;    (DOLIST (NUM NUMLIST)
;       (SETQ SUM (+ SUM NUM))))  ;; or maybe (INCF SUM NUM)
;
;
;of course, there is always:
;
;(DEFUN SUM (NUMLIST)
;   (COND ((NULL NUMLIST) 0)
;         (T (+ (FIRST NUMLIST) (SUM (CDR NUMLIST))))))
;
;    I think it's obvious that the last would be slow.
;    Also it's Obvious that there are Many ways to do this.
;What is the BEST (for speed and/or elegance) way to sum a list??
;
;(I Run Gold Hills Common 3.0 on a Compaq 386/20 with a 387)
;
;Thanks,    Brynn Rogers   rogers@src.honeywell.com

Why make life difficult?

<cl> (setq numlist '(1 2 3 6 7))

(1 2 3 6 7) 
<cl> (apply #'+ numlist)

19 

this was too easy since #'+ takes an arbitrary number of arguments.
Say it took only two arguments... A general way to handle this in
common lisp is with reduce:

<cl> (reduce #'+ numlist)

19 

;rob

  Robert C. Pettengill, MCC Software Technology Program
  P. O. Box 200195, Austin, Texas  78720
  ARPA:  rcp@mcc.com            PHONE:  (512) 338-3533
  UUCP:  {ihnp4,seismo,harvard,gatech,pyramid}!ut-sally!im4u!milano!rcp

johnson@csli.STANFORD.EDU (Mark Johnson) (10/27/88)

Ah, comparing alternative programs accross different machines
is always fun stuff!

I just ran your code (slightly modified as shown below) and
obtained the following results under Allegro CL on a Mac II.
Interestingly, the non-tail recursive version (as originally
provided) is faster than the tail-recursive one!  (Or have I
made an error in the coding?)

Mark Johnson

Preferred return address: johnson@csc.brown.edu

Welcome to Allegro CL Version 1.2.1!
? (setq list nil)
NIL
? (dotimes (i 1000) (push (- 1000 i) list))
NIL
? list
(1 2 3 4...
Aborted
? (length list)
1000
? (sum-test list)
(NOTHING) took 0 ticks (0.000 seconds) to run.
(EVAL-+) took 739 ticks (12.317 seconds) to run.
(DO-LOOP) took 111 ticks (1.850 seconds) to run.
(RECURSIVE) took 315 ticks (5.250 seconds) to run.
(TRECURSIVE) took 357 ticks (5.950 seconds) to run.
(RECURSIVE1) took 170 ticks (2.833 seconds) to run.
(TRECURSIVE1) took 220 ticks (3.667 seconds) to run.
(APPLY-+) took 55 ticks (0.917 seconds) to run.
(REDUCE-+) took 375 ticks (6.250 seconds) to run.
NIL
? 

(defun sum-test (list &optional (count 100))
  (macrolet ((repeat (&body body) `(dotimes (i count) do (progn .,body)))   
             (time-it (form) `(#+symbolics without-interrupts
                               #-symbolics progn                   
                               (time ,form))))
      
    (flet ((my-false (&rest x)                                  
             (declare (ignore x))
             nil))
      (flet ((nothing () (repeat (my-false list)))
             (do-loop () (repeat (let ((sum 0)) (dolist (item list) (incf sum item)) sum)))
             (recursive ()
               (labels ((recursive-call (list)
                          (if (null list) 0
                              (+ (car list) (recursive-call (cdr list))))))
                 (repeat (recursive-call list))))
             (trecursive ()
               (labels ((trecursive-call (list sum)
                          (if (null list) sum
                              (trecursive-call (cdr list) (+ (car list) sum)))))
                 (repeat (trecursive-call list 0))))
             (recursive1 () (repeat (recursive1-call list)))
             (trecursive1 () (repeat (trecursive1-call list 0)))
             (eval-+ () (repeat (eval (cons '+ list))))
             (apply-+ () (repeat (apply #'+ list)))
             (reduce-+ () (repeat (reduce #'+ list))))
        (time-it (nothing))
        (time-it (eval-+))
        (time-it (do-loop))
        (time-it (recursive))
        (time-it (trecursive))
        (time-it (recursive1))
        (time-it (trecursive1))
        (time-it (apply-+))
        (time-it (reduce-+))))))

(declare (inline recursive1-call trecursive1-call))

(defun recursive1-call (list)
  (if (null list) 0
      (+ (car list) (recursive1-call (cdr list)))))

(defun trecursive1-call (list sum)
  (if (null list) sum
      (trecursive1-call (cdr list) (+ (car list) sum))))

robv@pitstop.UUCP (Rob Vollum) (10/27/88)

In article <10794@srcsip.UUCP> rogers@eagle.UUCP (Brynn Rogers) writes:

> I Have a silly question.   I need to take the sum of a list 
> of numbers.
> (SETQ NUMLIST '(1 2 3 6 7))
> This is quite simple, really, but what is the BEST way to do it?
> I like: 
> 
> (EVAL (CONS '+ NUMLIST))
>
> But someone else says this would be faster::
>  
	[...iteration and recursion code deleted...]

How about (apply #'+ numlist)?

Besides being simple and clear, it is usually only a bit more
overhead than an explicit call to the function being APPLY'd. In
many cases, if the compiler is clever (and/or the programmer
makes declarations about the function being APPLY'd), it is *no*
additional overhead.

Rob Vollum
Sun Microsystems
Lexington, MA

sun!sunne!robv  or  rvollum@sun.com

robv@pitstop.UUCP (Rob Vollum) (10/27/88)

In article <10813@srcsip.UUCP> rogers@orion.UUCP (Brynn Rogers) writes:

>(EVAL (CONS '+ NUMLIST)) which (no surprise here) wasn't any faster
>Is there a better way?? (I think there has got to be)

>Brynn Rogers      rogers@src.honeywell.com
>P.S. I apoligize for being a novice poster.  But I have to learn somtime :-)

One rule of thumb that I use when programming in Lisp is that if you
find yourself wanting to call EVAL explicitly, you are probably doing
something wrong -- there will almost always be a better way to solve your
problem than resorting to user-controlled "double evaluation" (args being
EVAL's once (since EVAL is a function) then EVAL's again (as a result
of EVAL)). Of course, there are the other problems, such as EVAL not being
able to "see" lexical variables, etc.

Rob Vollum
Sun Microsystems
Lexington, mA

UUCP: sun!sunne!robv
ARPA: rvollum@sun.com

farquhar@cs.utexas.edu (Adam Farquhar) (10/28/88)

Stylistically (reduce #'+ list) seems to be the best way to sum up the
elements of a list.  I have often been frustrated, however, by its
inability to take the normal keyword arguments for sequence functions.
For example, one would like to be able to say
	(reduce #'+ (list box1 box2 box3 box4) :key #'box-weight)
Does anyone know why :key was left out?  Is there an elegant way to do
this in CL?

Adam Farquhar

barmar@think.COM (Barry Margolin) (10/29/88)

In article <3780@cs.utexas.edu> farquhar@cs.utexas.edu (Adam Farquhar) writes:
>For example, one would like to be able to say
>	(reduce #'+ (list box1 box2 box3 box4) :key #'box-weight)
>Does anyone know why :key was left out?  Is there an elegant way to do
>this in CL?

I don't know why :KEY was left out.  In my opinion, the best way to do
this currently is

	(flet ((+-weight (x y)
		 (+ (box-weight x) (box-weight y))))
	  (reduce #'+-weight ...))


Barry Margolin
Thinking Machines Corp.

barmar@think.com
{uunet,harvard}!think!barmar

hoey@ai.etl.army.mil (Dan Hoey) (11/01/88)

In article <29856@think.UUCP> barmar@kulla.think.com.UUCP (Barry Margolin)
	writes:
...
>I don't know why :KEY was left out.  In my opinion, the best way to do
>this currently is

>	(flet ((+-weight (x y)
>		 (+ (box-weight x) (box-weight y))))
>	  (reduce #'+-weight ...))

The problem there is that if you do that with more than two elements, you end
up trying to take the box-weight of the sum of two box-weights, and numbers
aren't boxes.  The ``right'' way is

	(flet ((+-weight (x y)
		 (+ x (box-weight y))))
	  (reduce #'+-weight ... :initial-value 0))

Guy has explained the omission of :KEY based on some feature of REDUCE, but I
don't remember it being extremely convincing.

Dan

will@uoregon.uoregon.edu (William Clinger) (11/01/88)

My apologies for continuing this discussion, but I grew tired of seeing
timings without analysis and I thought I might as well prepare a lecture
for this weird "Programming in Lisp" course I have to teach...
 
    I...obtained the following results under Allegro CL on a Mac II.
    Interestingly, the non-tail recursive version (as originally
    provided) is faster than the tail-recursive one!  (Or have I
    made an error in the coding?)
 
    Mark Johnson

Putting Mark's data with my measurements on a Macintosh II shows some of
the dangers of generalizing from one implementation:

                 Common Lisp    Scheme     comment

    NOTHING           .00          .02     no-op
    DO-LOOP          1.85         6.92     loop using an assignment
    D0-LOOP1         2.85 *       1.07     loop using do
    TRECURSIVE       5.95         1.08     tail-recursive, local procedure
    TRECURSIVE1      3.67         1.05     tail-recursive, global procedure
    RECURSIVE        5.25         3.40     non-tr, local procedure
    RECURSIVE1       2.83         3.72     non-tr, global procedure
    REDUCE-+         6.25        15.97     (reduce + list1000)
    APPLY-+           .92         ---      (apply + list1000)
    EVAL-+          12.32      6106.78     (eval (cons '+ list1000))

Considering Mark's question first, I too would have expected the
tail-recursive version to be faster than the non-tail-recursive version,
as it was in Scheme.  Part of the answer, I think, is that Allegro CL
does a pretty good job with non-tail-recursion but doesn't compile tail
recursion as efficiently as it might.  Another thing to consider is that
the tail-recursive version has an extra argument to deal with.  Evidently
the overhead of passing that extra argument is about the same as the
extra cost of non-tail-recursion compared to tail recursion in Allegro CL.
MacScheme, on the other hand, does a poor job with non-tail-recursion so
the extra argument is insignificant by comparison.

While some might consider APPLY the most elegant solution, and it appears
to be the fastest in Allegro CL, it isn't a portable solution.
Implementations of Common Lisp are explicitly allowed to place limits on
the number of arguments passed to a procedure, and the limit may be as
small as 50.  The Scheme language doesn't say anything about this, but
MacScheme has such a limit anyway (about 250).

Some Common Lisps compile tail-recursion as though it were
non-tail-recursion, so TRECURSIVE and TRECURSIVE1 are not portable
either in Common Lisp if you may have to deal with long lists.

EVAL is a pretty clear loser, but why did MacScheme take almost two hours?
Most implementations of Common Lisp use an interpretive EVAL, but Scheme
systems often use a compiling EVAL.  Furthermore the MacScheme compiler
has a minor bug that makes the worst-case compile time quadratic, rather
than linear.  What's the bug?  "If we're compiling an expression that looks
like (+ E1 E2 ...), and its LENGTH is greater than 2, then change it to
(+ (+ E1 E2) ...) and try again."  In other words, EVAL-+.

In Scheme you can pretty well count on DO-LOOP1, TRECURSIVE, and
TRECURSIVE1 compiling into nearly identical code because they usually
are expanded into nearly identical code before the compiler proper ever
sees them.  TRECURSIVE1 might be slower because fetching the global
value of TRECURSIVE1 for the tail-recursive call may involve an actual
variable reference, while the local variable references for the other
two would certainly be optimized away.  It seems like the same should be
true of Common Lisp, but in fact many CL compilers treat do loops and
top-level procedures specially, leaving locally defined procedures to
the mercy of the compiler's most general algorithms.  With such a compiler
I would expect DO-LOOP1 to be fastest and TRECURSIVE slowest, which is
what we observe.  This probably explains also why RECURSIVE was slower
than RECURSIVE1 in Common Lisp.

Using REDUCE for this problem means calling the general version of +,
which I would expect to be slow because it involves a rest argument.
It might be slow for other reasons also, depending on how REDUCE is
coded.  Common Lisp was only twice as slow for REDUCE-+ as for RECURSIVE1,
which isn't too bad.

I wrote REDUCE for Scheme, using a subset of the CL semantics.  A curried
REDUCE (e.g. ((REDUCE +) LIST1000) instead of (REDUCE + LIST1000)) would
have been more in the spirit of Scheme and would not have made any
significant difference to the timings.  In my opinion a curried REDUCE
supplies the most elegant solution to the problem of summing a list:
(DEFINE MY-LIST-SUMMATION-PROCEDURE (REDUCE +)).  It's also the slowest
of the reasonable solutions.  The fastest portable solution is
tail-recursion for Scheme and some kind of DO loop for Common Lisp.

The obvious explanation for the DO-LOOP anomaly is that the Scheme version
uses a procedure, FOR-EACH, while the CL version uses a macro, DOLIST,
causing the Scheme version to execute 100,000 full-scale procedure calls
compared with none for the CL version.  I wrote DO-LOOP1 as a similar
benchmark that could be translated more easily between the two languages.
The starred Common Lisp timing was mine, not Mark's, and thus may not be
directly comparable to the others in the CL column.

Peace,
William Clinger
an author of MacScheme

Scheme code (assuming a timeit macro):

(define (sum-test list . rest)
  (let ((count (if (null? rest) 100 (car rest))))
    (define (repeat thunk)
      (define (loop n)
        (if (zero? n)
            'done
            (begin (thunk) (loop (- n 1)))))
      (loop count))
    (define (my-false . x) #f)
    (define (nothing)
      (repeat (lambda () (my-false list))))
    (define (do-loop)
      (repeat (lambda ()
                (let ((sum 0))
                  (for-each (lambda (item) (set! sum (+ sum item)))
                            list)
                  sum))))
    (define (do-loop1)
      (repeat (lambda ()
                (do ((sum 0 (+ sum (car list)))
                     (list list (cdr list)))
                    ((null? list) sum)))))
    (define (recursive)
      (define (recursive-call list)
        (if (null? list)
            0
            (+ (car list) (recursive-call (cdr list)))))
      (repeat (lambda () (recursive-call list))))
    (define (trecursive)
      (define (trecursive-call list sum)
        (if (null? list)
            sum
            (trecursive-call (cdr list) (+ (car list) sum))))
      (repeat (lambda () (trecursive-call list 0))))
    (define (recursive1)
      (repeat (lambda () (recursive1-call list))))
    (define (trecursive1)
      (repeat (lambda () (trecursive1-call list 0))))
    (define (eval-+) (repeat (lambda () (eval (cons '+ list)))))
    (define (apply-+) (repeat (lambda () (apply + list))))
    (define (reduce-+) (repeat (lambda () (reduce + list))))
    (timeit (nothing))
    (timeit (do-loop))
    (timeit (do-loop1))
    (timeit (recursive))
    (timeit (trecursive))
    (timeit (recursive1))
    (timeit (trecursive1))
    (timeit (reduce-+))
    ;(timeit (apply-+))
    (timeit (eval-+))))
 
(define (recursive1-call list)
  (if (null? list)
      0
      (+ (car list) (recursive1-call (cdr list)))))
 
(define (trecursive1-call list sum)
  (if (null? list)
      sum
      (trecursive1-call (cdr list) (+ (car list) sum))))

(define (reduce f l)
  (define (loop x l)
    (if (null? l)
        x
        (loop (f x (car l)) (cdr l))))
  (loop (car l) (cdr l)))

(define (iota n)
  (do ((n n (1- n))
       (l '() (cons n l)))
      ((zero? n) l)))

(define x (iota 1000))

(sum-test x)

pf@csc.ti.com (Paul Fuqua) (11/01/88)

    Date: Wednesday, October 26, 1988  11:23am (CDT)
    From: barmar at think.COM (Barry Margolin)
    Subject: Re: Summing a list
    Newsgroups: comp.lang.lisp
    
    I decided to time all the various methods that have been discussed.  I
    tried them on a Symbolics 3640 running Genera 7.2 and a Sun 3/280
    running Lucid CL 2.0.3.  I used the default OPTIMIZE parameters.

To add another implementation to the pot, I ran roughly the same code on
a TI Explorer 2 running release 4.1+, also with the default
optimisations.  I included Mark Johnson's tail-recursive versions, and
both helper-function and LABELS versions of the original recursive code.

The fastest were DO-LOOP, APPLY-+, and TRECURSIVE (tail-recursion using
LABELS).  The latter is up there because the compiler managed to
open-code the recursive calls into a loop, so all three are running
essentially the same code.

Next in line are RECURSIVE1 and TRECURSIVE1 (two helper-function
recursive versions), and REDUCE-+, all about 7 times as long.  No
open-coding here, it's all function-calling speed.

The slowpoke of the bunch was RECURSIVE (Barry Margolin's original
code), at about 13 times as long, because it's forming and discarding
lexical closures on each function call (all stack-consing, though).  It
was this surprising result that led me to examine the code.

[I was unable to run EVAL-+, because the evaluator spread the whole list
onto the stack and exceeded the 256-word limit on stack frames.
(APPLY-+ doesn't do that, because it's applying a function that takes a
&REST argument.)  On a shorter list, it was about 6 times as long as
DO-LOOP.]

                              pf

Paul Fuqua
Texas Instruments Computer Science Center, Dallas, Texas
CSNet:  pf@csc.ti.com (ARPA too, sometimes)
UUCP:   {smu, texsun, cs.utexas.edu, im4u, rice}!ti-csl!pf

skef@SKEF.SLISP.CS.CMU.EDU (Skef Wholey) (11/02/88)

In article <200@ai.etl.army.mil>, hoey@ai.etl.army.mil (Dan Hoey) writes:
> In article <29856@think.UUCP> barmar@kulla.think.com.UUCP (Barry Margolin)
> 	writes:
> >... I don't know why :KEY was left out ...
> ... The ``right'' way is
> 	(flet ((+-weight (x y)
> 		 (+ x (box-weight y))))
> 	  (reduce #'+-weight ... :initial-value 0))
> Guy has explained the omission of :KEY based on some feature of REDUCE,
> but I don't remember it being extremely convincing. ...

The reasoning is this: in all other sequence functions, the :KEY function
is applied to the operands of the test (either :TEST, :TEST-NOT, or the
PREDICATE argument to an -IF or -IF-NOT function) -- see p. 247 of CLtL.
To have :KEY do a kind of selection in REDUCE rather than a filtering
operation would have destroyed this consistency.  I don't know if this is
"extremely convincing", but there is something to be said for keeping what
consistency CL has...

Oh, my vote for doing what you'd want to do:

    (reduce #'+ (map 'list #'box-weight ...))

Any "good" compiler should "do the right thing" with this.  (Only 1/2 :-]
here -- it is not really difficult to generate good code for stuff like
that.)

--Skef