From: Eric L. Raible
Subject: permutations
Date: 
Message-ID: <1131@amelia.nas.nasa.gov>
(defun permutations (elements)
  (if (null elements)
      (list nil)
      (mapcan
       #'(lambda (element)
	   (mapcar
	    #'(lambda (permutation)
		(cons element permutation))
	    (permutations (remove element elements))))
       elements)))

Comments?  Alternatives?

From: Stephen E. Miner
Subject: Re: permutations
Date: 
Message-ID: <14337@joyce.istc.sri.com>
In article <····@amelia.nas.nasa.gov> ······@orville.nas.nasa.gov (Eric L. Raible) writes:
>
>(defun permutations (elements)
>  (if (null elements)
>      (list nil)
>      (mapcan
>       #'(lambda (element)
>	   (mapcar
>	    #'(lambda (permutation)
>		(cons element permutation))
>	    (permutations (remove element elements))))
>       elements)))
>
>Comments?  Alternatives?

Here's an alternative...


(defun propagate (element perm)
  "Returns a list of 'propagations' of the ELEMENT through the list PERM."
  (propagate-aux element nil perm))

(defun propagate-aux (element before after)
  "Returns a list of lists each with the prefix BEFORE followed by one of the
possible insertions of ELEMENT into the list AFTER." 
  (if (endp after) 
      (list (append before (list element)))
      (cons (append before (cons element after))
            (propagate-aux element 
		           (append before (list (car after))) 
		           (cdr after)))))

(defun permu-extend (element permu-list)
  "Returns an extended list of permutations by propagating the new
ELEMENT through each of the base permutations in PERMU-LIST."
  (if (endp permu-list)
      nil
      (append (propagate element (car permu-list))
	      (permu-extend element (cdr permu-list)))))

(defun permu (elements)
  "Returns a list of the permutations of the list ELEMENTS."
  (if (endp elements) 
      (list nil)
      (permu-extend (car elements) (permu (cdr elements)))))



Stephen E. Miner
·····@sri.com

	       *** My other computer is a Macintosh ***
From: Basalat Ali Raja
Subject: Re: permutations
Date: 
Message-ID: <2066@kalliope.rice.edu>
···········@umbc3.umd.edu writes
>	I would have liked to see alternative suggestions for the permutations
>function in lisp, and would have tried to offer some if I wasn't so busy right
>now. I don't care much for the map* functions, and am always looking at
>alternate styles to code mapping problems. "My language is better then your
>language" I really don't need.

Here is one more solution to the permutations problem.

(defun sub-perm (prev el after)
        (if (not (null? after))
            (append (sprinkle el (permutation (append prev after)))
                    (sub-perm (reverse (cons el (reverse prev)))
                              (car after)
                              (cdr after)
                    )
            )
            ()
         )
)

; where sprinkle is defined as:

(defun sprinkle (el plist)
        (mapcar (lambda (one-p) (cons el one-p)) plist)
)

; and the permutation function is, of course:

(defun permutation (l)
        (if (null? l)
            ()
            (sub-perm () (car l) (cdr l))
        )
)

Please excuse my syntax; it's a Scheme programmer trying to 
write in plain Lisp (I am sure there is some version out there
that can take this, somewhere.....)

The code is not guaranteed; it's been a long time since I had
need for this, but I think the general idea is correct.

Summary of solution:
	Foreach element E in a list L to be permuted
		Permute L without E.
		Cons E to the beginning of each permuted 
		list from the above result.
		
	Append all the sub-lists from the above together.

Sincerely,
·······@cleo.rice.edu
From: J.R.G.Cupitt
Subject: Re: permutations
Date: 
Message-ID: <5671@eagle.ukc.ac.uk>
In article <····@amelia.nas.nasa.gov> ······@orville.nas.nasa.gov (Eric L. Raible) writes:
}(defun permutations (elements)
}  (if (null elements)
}      (list nil)
}      (mapcan
}       #'(lambda (element)
}	   (mapcar
}	    #'(lambda (permutation)
}		(cons element permutation))
}	    (permutations (remove element elements))))
}       elements)))
}
}Comments?  Alternatives?

Good grief! I almost collapsed when I saw this .. I realise that this is a
LISP group, but I can't resist posting the same algorithm in Miranda:

	perms :: [*] -> [[*]]
	perms x	= [[]], x = []
		= [ a:p | a <- x; p <- perms (x--[a]) ], otherwise

John Cupitt
From: Brynn Rogers
Subject: Summing a list
Date: 
Message-ID: <10794@srcsip.UUCP>
 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   ······@src.honeywell.com
From: Brynn Rogers
Subject: Re: Summing a list
Date: 
Message-ID: <10813@srcsip.UUCP>
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      ······@src.honeywell.com
P.S. I apoligize for being a novice poster.  But I have to learn somtime :-)
From: Juergen Wagner
Subject: Re: Summing a list
Date: 
Message-ID: <6135@csli.STANFORD.EDU>
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,		   ·······@csli.stanford.edu
Center for the Study of Language and Information (CSLI), Stanford CA
From: Barry Margolin
Subject: Re: Summing a list
Date: 
Message-ID: <29718@think.UUCP>
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.

······@think.com
{uunet,harvard}!think!barmar
From: Mark Johnson
Subject: Re: Summing a list
Date: 
Message-ID: <6143@csli.STANFORD.EDU>
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: ·······@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))))
From: William Clinger
Subject: Re: Summing a list
Date: 
Message-ID: <3065@uoregon.uoregon.edu>
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)
From: Paul Fuqua
Subject: Re: Summing a list
Date: 
Message-ID: <62445@ti-csl.CSNET>
    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:  ··@csc.ti.com (ARPA too, sometimes)
UUCP:   {smu, texsun, cs.utexas.edu, im4u, rice}!ti-csl!pf
From: Andreas Girgensohn
Subject: Re: Summing a list
Date: 
Message-ID: <4293@boulder.Colorado.EDU>
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
········@boulder.colorado.edu
From: Rob Vollum
Subject: Re: Summing a list
Date: 
Message-ID: <249@pitstop.UUCP>
In article <·····@srcsip.UUCP> ······@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      ······@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: ·······@sun.com
From: Eliot Handelman
Subject: Scope of EVAL (was: Re: Summing a list)
Date: 
Message-ID: <4154@phoenix.Princeton.EDU>
In article <···@pitstop.UUCP> ····@pitstop.UUCP (Rob Vollum) writes:

>Of course, there are the other problems, such as EVAL not being
>able to "see" lexical variables, etc.

Is that really true?  In the following example, EVAL consults the lexical
environment, rather that the global.

(setq x nil)

And now (let* ((x t) (y x)) (eval y)) => t

The result of the first evalution sets y to x; yet EVAL gets the effective
lexical binding anyway. This also seems to work whether or not the code is
compiled and x is made special.  Can you give an example where that
isn't the case?

Eliot Handelman
Music, Princeton U.
From: Andreas Girgensohn
Subject: Re: Scope of EVAL (was: Re: Summing a list)
Date: 
Message-ID: <4345@boulder.Colorado.EDU>
In article <····@phoenix.Princeton.EDU> ·····@phoenix.Princeton.EDU (Eliot Handelman) writes:
>Is that really true?  In the following example, EVAL consults the lexical
>environment, rather that the global.
>
>(setq x nil)
>
>And now (let* ((x t) (y x)) (eval y)) => t

EVAL evaluates its argument so that the above call of eval is the same
as (eval 't).  (eval 'y) will lead to an error unless y is a special
variable.

Andreas Girgensohn
········@boulder.colorado.edu
From: David A Duff
Subject: Re: Scope of EVAL (was: Re: Summing a list)
Date: 
Message-ID: <12473@steinmetz.ge.com>
In article <····@phoenix.Princeton.EDU>, ·····@phoenix (Eliot Handelman) writes:
>In article <···@pitstop.UUCP> ····@pitstop.UUCP (Rob Vollum) writes:

[... stuff about eval only being able to perform evaluation in the top-level
environment.] 

>Is that really true?  In the following example, EVAL consults the lexical
>environment, rather that the global.

Yes.

>(setq x nil)
>And now (let* ((x t) (y x)) (eval y)) => t

Remember: eval is a function, and the semantics of lisp are such that when
evaluating a function application (a list whose car is neither a macro nor a
special form), the arguments are evaluated first, then the function is
applied.  So, basically, whatever you put in place of ... in "(eval ...)" ends
up getting evaluated TWICE -- once before eval is called and once after.  In
your example above, the eval function never sees the symbol y, but is instead
passed the value t.  

To better illustrate the difference between evaluation within a lexical
environment and evaluation in the top-level environment (the kind that the
lisp eval function does) you probably meant to try something like this:

(setq x nil)

;; here x is eval'd in lexical environment:
(let ((x t)) x) ==> t 

;; here x is eval'd in top-level environment:
(let ((x t)) (eval 'x)) ==> nil

Dave Duff                                     GE Research and Development Center
····@eraserhead.steinmetz.ge.com                           Schenectady, New York
uunet!steinmetz!eraserhead!duff                                     518-387-5649
Dave Duff                                     GE Research and Development Center
····@eraserhead.steinmetz.ge.com                           Schenectady, New York
uunet!steinmetz!eraserhead!duff                                     518-387-5649
From: Rob Vollum
Subject: Re: Scope of EVAL (was: Re: Summing a list)
Date: 
Message-ID: <254@pitstop.UUCP>
In article <····@phoenix.Princeton.EDU> ·····@phoenix.Princeton.EDU (Eliot Handelman) writes:
>In article <···@pitstop.UUCP> ····@pitstop.UUCP (Rob Vollum) writes:
>
>>Of course, there are the other problems, such as EVAL not being
>>able to "see" lexical variables, etc.
>
>Is that really true?  In the following example, EVAL consults the lexical
>environment, rather that the global.
>
>(setq x nil)
>And now (let* ((x t) (y x)) (eval y)) => t
>
>The result of the first evalution sets y to x; yet EVAL gets the effective
>lexical binding anyway. This also seems to work whether or not the code is
>compiled and x is made special.  Can you give an example where that
>isn't the case?
>
>Eliot Handelman

In the example given above, you're not really EVALing a symbol; you're EVALing
the value of a symbol. Things worked out (in this case) because T is 
self-evaluating. If you had tried (let* ((x 'a) (y x)) (eval y)) you would
have gotten an error along the lines of "symbol A has no global value..."

To illustrate the point that EVAL cannot see the lexical environment, try this:

(setq x 'global-value)
(let ((x 'lexical-value)) (eval 'x))
--> GLOBAL-VALUE

(and remember, the initial SETQ *must* be a SETQ, and not a DEFVAR, since DEFVAR
proclaims things SPECIAL, after which they can never be lexical.)

As to why EVAL might be specified not to see lexical values of symbols: compilers
don't deal with symbol names when accessing lexical variables, generally. They
deal only in stack offsets. In fact, in your example above, what's happening is
somewhere along the following lines: the compiler creates two slots on the stack;
one for x, one for y. When compiling the code for the "eval" expression, it 
generates something like "load the contents of stack-pointer+2". It never
mentions Y at all. So, when EVALing symbols at run-time, the system really has
no choice but to grab the top-level value.

Rob Vollum
UUCP: ...sun!sunne!robv
ARPA: ·······@sun.com
From: Adam Farquhar
Subject: Re: Summing a list
Date: 
Message-ID: <3780@cs.utexas.edu>
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
From: Barry Margolin
Subject: Re: Summing a list
Date: 
Message-ID: <29856@think.UUCP>
In article <····@cs.utexas.edu> ········@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.

······@think.com
{uunet,harvard}!think!barmar
From: Dan Hoey
Subject: Re: Summing a list
Date: 
Message-ID: <200@ai.etl.army.mil>
In article <·····@think.UUCP> ······@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
From: Skef Wholey
Subject: Re: Summing a list
Date: 
Message-ID: <3467@pt.cs.cmu.edu>
In article <···@ai.etl.army.mil>, ····@ai.etl.army.mil (Dan Hoey) writes:
> In article <·····@think.UUCP> ······@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
From: Eric A. Raymond
Subject: Re: Summing a list
Date: 
Message-ID: <17109@ames.arc.nasa.gov>
In article <·····@srcsip.UUCP> ······@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: ·······@pioneer.arc.nasa.gov
SLOW: NASA Ames Research Center, MS 244-17, Moffett Field, CA 94035

Nothing left to do but :-) :-) :-)
From: Rob Pettengill
Subject: Re: Summing a list
Date: 
Message-ID: <1457@perseus.>
In article <·····@srcsip.UUCP> ······@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   ······@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:  ···@mcc.com            PHONE:  (512) 338-3533
  UUCP:  {ihnp4,seismo,harvard,gatech,pyramid}!ut-sally!im4u!milano!rcp
From: Rob Vollum
Subject: Re: Summing a list
Date: 
Message-ID: <248@pitstop.UUCP>
In article <·····@srcsip.UUCP> ······@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  ·······@sun.com
From: Alex S. Crain
Subject: Re: permutations
Date: 
Message-ID: <1295@umbc3.UMD.EDU>
In article <····@eagle.ukc.ac.uk> ···@ukc.ac.uk (J.R.Cupitt) writes:

	[lisp code for permutations function deleted]

>Good grief! I almost collapsed when I saw this .. I realise that this is a
>LISP group, but I can't resist posting the same algorithm in Miranda:

	[miranda code for permutations function deleted]

	I don't understand the motive behind this. matrix multiplication
is easier in Berkeley fp than it is in Lisp, but that doesn't make it a 
superior language. The permutation function is probably easy in APL too...

	I can understand the taunts from POPLOG users, in that POPLOG is all
of CL plus an alternate interface (several in fact) and while I've never used
POPLOG, it sounds like a nice extension package to CL, which could prove 
useful in certain situations. My understanding of Miranda, however, is that
it is a purely functional language, and therefore not directly related to
CL, which lost most of its function roots long ago. 

	I would have liked to see alternative suggestions for the permutations
function in lisp, and would have tried to offer some if I wasn't so busy right
now. I don't care much for the map* functions, and am always looking at
alternate styles to code mapping problems. "My language is better then your
language" I really don't need.




-- 
					:alex.
					Systems Programmer
···········@umbc3.umd.edu		UMBC
····@umbc3.umd.edu
From: Mark Johnson
Subject: Re: permutations
Date: 
Message-ID: <6139@csli.STANFORD.EDU>
Here's an alternative definition of permute which avoids all use of
assignment operations.  Note that the original definition of
permute in terms of mapping operations did this too.  I much
prefer the original definition to the one I give below, but you said
you want to see alternatives, so here goes...

(Just in case you're wondering, this style of programming comes from
trying to write Lisp programs the same way you'd write a Prolog
program).

(defun permute (list)
  (if list
    (inserts (first list) (permute (rest list)))
    '(()) ))

(defun inserts (elt lists)
  (if lists
    (append (if (null (first lists))
              (list (list elt))
              (cons (cons elt (first lists))
                    (prepends (first (first lists))
                              (inserts elt (list (rest (first lists)))))))
            (inserts elt (rest lists)))
    '() ))

(defun prepends (elt lists)
  (if lists
    (cons (cons elt (first lists))
          (prepends elt (rest lists)))
    '()))


#| 

;;; Original definitions of inserts and prepends, from which the
definitions
;;; above are obtained by unfolding with respect to insert and append
respectively.

(defun inserts (elt lists)
  (if lists
    (append (insert elt (first lists))
            (inserts elt (rest lists)))
    '()))

(defun insert (elt list)
  (if (null list)
    (list (list elt))
    (cons (cons elt list)
          (prepends (first list)
                    (insert elt (rest list))))))

(defun prepends (elt lists)
  (if lists
    (cons (prepend elt (first lists))
          (prepends elt (rest lists)))
    '()))

(defun prepend (elt list)
  (cons elt list))

|#