From: Steven E. Harris
Subject: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q67he2vqhfx.fsf@raytheon.com>
I'm stuck trying to wrap some functions and macros taking &rest
parameters, and I can't figure out how to use &rest parameters more
than once while avoiding multiple evaluation. I'll explain with some
simplified examples.

First take this function that does something kind of command-line
composition and execution:

(defun execute-cmd (cmd &rest args)
  (format nil "~A~{ ~A~}" cmd args))


Now, here's a little wrapper macro to bind the result of command
execution and use the result within a provided body:

(defmacro with-cmd-result ((var cmd &rest args) &body body)
  `(let ((,var (execute-cmd ,cmd ,@args)))
    ,@body))


We can call it like this:

(with-cmd-result (res "foo" "bar" "baz")
  (format nil "result: ~A" res))


Fine. Now imagine some companion function for tracing command
execution:

(defun trace-cmd (res cmd &rest args)
  (format *trace-output* "cmd: ~A~{ ~A~} => ~A" cmd args res))


We'd like to layer it on top of the with-cmd-result macro above like
this:

(defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
  `(with-cmd-result (,var ,cmd ,@args)  ; eval 1
    (progn
      (trace-cmd ,var ,cmd ,@args)      ; eval 2
      ,@body)))


We would call this one as:

(with-cmd-result-traced (res "foo" "bar" (make-some-other-arg))
  (format nil "result: ~A" res))


It almost works. Of course, this is wrong because both cmd and args
are evaluated twice. We need to introduce gensyms, evaluate the
arguments once, and use the gensyms throughout. Here is where I start
flailing:

;; Attempt 1 - non-thinking translation
(defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
  (port:with-gensyms ("" gcmd gargs)
    `(let ((,gcmd ,cmd)
           (,gargs ,args))
      (with-cmd-result (,var ,gcmd ,@gargs)
        (progn
          (trace-cmd ,var ,gcmd ,@gargs)
          ,@body)))))


No, that doesn't unfold the gargs list properly. How about this:

;; Attempt 2 - expand args first
(defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
  (port:with-gensyms ("" gcmd gargs)
    `(let ((,gcmd ,cmd)
           (,gargs (list ,@args)))
      (with-cmd-result (,var ,gcmd ,gargs)
        (progn
          (trace-cmd ,var ,gcmd ,gargs)
          ,@body)))))


That's not right either. gargs gets passed in as a list, and doesn't
get unfolded. Let's add some more @s:

;; Attempt 2 - expand args first, then again
(defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
  (port:with-gensyms ("" gcmd gargs)
    `(let ((,gcmd ,cmd)
           (,gargs (list ,@args)))
      (with-cmd-result (,var ,gcmd ,@gargs)
        (progn
          (trace-cmd ,var ,gcmd ,@gargs)
          ,@body)))))


Now only the first element in args makes it through.

At this point, I'm just reaching in the dark like a beginning C
programmer stabbing the * and & keys. When dealing with functions
rather than macros, I see how apply helps forward on these &rest
parameters. Here, I can't use apply because I'm trying to forward
arguments from one macro to another.

I'm trying to keep the tracing stuff separate from the execution
stuff. The latter is low-level stuff that already works; the former is
just a higher-level debugging aid that should just layer in. That
means that I don't want to call trace-cmd from execute-cmd.�

Am I missing a simple solution, or is my entire intent flawed? Advice
and criticism would be welcome.


Footnotes: 
� Again, the example is somewhat contrived. Instead of tracing, I'm
  really examining the command output to trap certain erroneous
  results and signal an appropriate condition. The command and
  arguments are used twice: once to execute the command, and again to
  create a condition that indicates both the error output and the
  motivating command.

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com

From: Kenny Tilton
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <3F78DBB7.8040103@nyc.rr.com>
Steven E. Harris wrote:

> I'm stuck trying to wrap some functions and macros taking &rest
> parameters, and I can't figure out how to use &rest parameters more
> than once while avoiding multiple evaluation. I'll explain with some
> simplified examples.
> 
> First take this function that does something kind of command-line
> composition and execution:
> 
> (defun execute-cmd (cmd &rest args)
>   (format nil "~A~{ ~A~}" cmd args))
> 
> 
> Now, here's a little wrapper macro to bind the result of command
> execution and use the result within a provided body:
> 
> (defmacro with-cmd-result ((var cmd &rest args) &body body)
>   `(let ((,var (execute-cmd ,cmd ,@args)))
>     ,@body))
> 
> 
> We can call it like this:
> 
> (with-cmd-result (res "foo" "bar" "baz")
>   (format nil "result: ~A" res))
> 
> 
> Fine. Now imagine some companion function for tracing command
> execution:
> 
> (defun trace-cmd (res cmd &rest args)
>   (format *trace-output* "cmd: ~A~{ ~A~} => ~A" cmd args res))
> 
> 
> We'd like to layer it on top of the with-cmd-result macro above like
> this:
> 
> (defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
>   `(with-cmd-result (,var ,cmd ,@args)  ; eval 1
>     (progn
>       (trace-cmd ,var ,cmd ,@args)      ; eval 2
>       ,@body)))
> 
> 
> We would call this one as:
> 
> (with-cmd-result-traced (res "foo" "bar" (make-some-other-arg))
>   (format nil "result: ~A" res))
> 
> 
> It almost works. Of course, this is wrong because both cmd and args
> are evaluated twice. We need to introduce gensyms, evaluate the
> arguments once, and use the gensyms throughout. Here is where I start
> flailing:
> 
> ;; Attempt 1 - non-thinking translation
> (defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
>   (port:with-gensyms ("" gcmd gargs)
>     `(let ((,gcmd ,cmd)
>            (,gargs ,args))
>       (with-cmd-result (,var ,gcmd ,@gargs)
>         (progn
>           (trace-cmd ,var ,gcmd ,@gargs)
>           ,@body)))))
> 
> 
> No, that doesn't unfold the gargs list properly. How about this:
> 
> ;; Attempt 2 - expand args first
> (defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
>   (port:with-gensyms ("" gcmd gargs)
>     `(let ((,gcmd ,cmd)
>            (,gargs (list ,@args)))
>       (with-cmd-result (,var ,gcmd ,gargs)
>         (progn
>           (trace-cmd ,var ,gcmd ,gargs)
>           ,@body)))))
> 
> 
> That's not right either. gargs gets passed in as a list, and doesn't
> get unfolded. Let's add some more @s:
> 
> ;; Attempt 2 - expand args first, then again
> (defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
>   (port:with-gensyms ("" gcmd gargs)
>     `(let ((,gcmd ,cmd)
>            (,gargs (list ,@args)))
>       (with-cmd-result (,var ,gcmd ,@gargs)
>         (progn
>           (trace-cmd ,var ,gcmd ,@gargs)
>           ,@body)))))
> 
> 
> Now only the first element in args makes it through.
> 
> At this point, I'm just reaching in the dark like a beginning C
> programmer stabbing the * and & keys. When dealing with functions
> rather than macros, I see how apply helps forward on these &rest
> parameters. Here, I can't use apply because I'm trying to forward
> arguments from one macro to another.

<heh-heh> Hairy stuff, indeed. Have you been macroexpanding, as well as 
putting print statements in both outside and inside the code returned by 
the macro?

(with-cmd-result-traced (res "foo" "bar" (make-some-other-arg))
   (format nil "result: ~A" res))

becomes (if you expand):

(let ((#:g1000 "foo")
      (#:g1001 (list "bar" (make-some-other-arg))))
   (with-cmd-result (res #:g1000 . #:g1001)
                    (progn (trace-cmd res #:g1000 . #:g1001)
                      (format nil "result: ~A" res))))

uh-oh. look at that dotted list, and the fact that CL expanded the 
non-lisp symbol into the argument list to with-cmd-result, not the 
run=time list that will be bound to it. Because of course this is not 
going on at run-time. You can do the ,@thing in someplaces because the 
reader is making up a list (of coded /forms/).

... and then expand again and then cut and paste

(let ((#:g1000 "foo") (#:g1001 (list "bar" (make-some-other-arg))))
   (let ((res (execute-cmd #:g1000 . #:g1001)))
     (progn (trace-cmd res #:g1000 . #:g1001)
            (format nil "result: ~A"   res))))

I can't help much more because I don't really get what is going on. I do 
not see how execute-cmd executes anything, and I am concerned that the 
expansion of the last form (double eval issues aside) will both 
execute-cmd and trace-cmd (or was trace-cmd meant literally to do no 
more than write to *trace-output*?)

what you probably need to do is something more like:

(defmacro with-cmd-result ((var &optional trace-p) cmd &rest args)
    ...

...and then, if trace-p is true, expand additional tracing code (or just 
include "(when ,trace-p (trace-cmd... "


> 
> I'm trying to keep the tracing stuff separate from the execution
> stuff. The latter is low-level stuff that already works; the former is
> just a higher-level debugging aid that should just layer in. That
> means that I don't want to call trace-cmd from execute-cmd.�
> 
> Am I missing a simple solution, or is my entire intent flawed? Advice
> and criticism would be welcome.

yer doing fine, actually. just keep whacking your head against the 
concrete, you're almost there.

kenny
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q67oex2p71w.fsf@raytheon.com>
Kenny Tilton <·······@nyc.rr.com> writes:

> Have you been macroexpanding, as well as putting print statements in
> both outside and inside the code returned by the macro?

Yes, but even though I can see the incorrect macroexpansions, I'm not
so sure I know what /should/ be there.

I still find &rest parameters difficult to understand. There's some
relationship between letting a &rest parameter build up a single list
of arguments versus forcing the caller to compose a list manually and
pass it as a single argument. Maybe it's "just style," but I have a
hard time deciding which idiom to use.

[...]

> I can't help much more because I don't really get what is going
> on. I do not see how execute-cmd executes anything,

It doesn't here. In my real code, it composes and writes the commands
out to a running subprocess (ext:make-pipe-io-stream in CLISP), wraps
a decorating stream around the pipe output stream, and returns that
stream for the caller to read. Sort of.

> was trace-cmd meant literally to do no more than write to
> *trace-output*?

That's it. But as I said, tracing is only one thing to layer in. More
importantly, I have a stream filter that watches for certain output
to signal an error. That needs to be optionally layered in as well.

> what you probably need to do is something more like:
>
> (defmacro with-cmd-result ((var &optional trace-p) cmd &rest args)
>     ...
>
> ...and then, if trace-p is true, expand additional tracing code (or
> just include "(when ,trace-p (trace-cmd... "

I thought of that, but then I have to mix two facilities that are for
now separated along the dependency graph.

> just keep whacking your head against the concrete, you're almost
> there.

Hey, at least it's not C++, right?

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: Barry Margolin
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <4jjeb.114$pd.58@news.level3.com>
In article <···············@raytheon.com>,
Steven E. Harris  <········@raytheon.com> wrote:
>Kenny Tilton <·······@nyc.rr.com> writes:
>
>> Have you been macroexpanding, as well as putting print statements in
>> both outside and inside the code returned by the macro?
>
>Yes, but even though I can see the incorrect macroexpansions, I'm not
>so sure I know what /should/ be there.
>
>I still find &rest parameters difficult to understand. There's some
>relationship between letting a &rest parameter build up a single list
>of arguments versus forcing the caller to compose a list manually and
>pass it as a single argument. Maybe it's "just style," but I have a
>hard time deciding which idiom to use.

It's just a convenience feature that allows for terser function calls.
There's no semantic difference between:

(defun fun1 (&rest args) ...)
(fun1 ...)

and

(defun fun2 (args) ...)
(fun2 (list ...))

Actually, there's one case where it does more than this: when you combine
&rest with &key, e.g.

(defun fun3 (&rest args &key key1 key2 &allow-other-keys) ...)

In this case, ARGS will contain a list of all the arguments (making it easy
to pass them on to another function), while KEY1 and KEY2 will pick up
those specific keyword arguments from within the list.

-- 
Barry Margolin, ··············@level3.com
Level(3), Woburn, 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: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q67smmck0rf.fsf@raytheon.com>
Barry Margolin <··············@level3.com> writes:

> There's no semantic difference between:
>
> (defun fun1 (&rest args) ...)
> (fun1 ...)
>
> and
>
> (defun fun2 (args) ...)
> (fun2 (list ...))

Let's say that fun1 is defined as

(defun fun1 (&rest args)
  (format nil "~{~A~^ ~}" args))

If I call (fun1 "foo" "bar" "baz"), I get

"foo bar baz"

as a "flat" list of concatenated strings. But what if I need to
compose my argument list at runtime? Consider this attempt:

(let ((flag 1))
  (fun1 "foo" "bar" (if (oddp flag)
                        "baz"
                        '("one" "two"))))

That begets "foo bar baz." But if flag is even, we get

"foo bar (one two)"

I'd like some way to produce the arguments to elicit

"foo bar one two"

Is it possible to flatten such an argument list /before/ it gets
collected in the foo1 &rest parameter, or is that flattening really
the job of foo1?

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: Matthew Danish
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <20031001232305.GF1454@mapcar.org>
On Wed, Oct 01, 2003 at 04:15:48PM -0700, Steven E. Harris wrote:
> (let ((flag 1))
>   (fun1 "foo" "bar" (if (oddp flag)
>                         "baz"
>                         '("one" "two"))))

(let ((flag 1))
  (apply 'fun1 "foo" "bar" (if (oddp flag) '("baz") '("one" "two"))))

-- 
; Matthew Danish <·······@andrew.cmu.edu>
; OpenPGP public key: C24B6010 on keyring.debian.org
; Signed or encrypted mail welcome.
; "There is no dark side of the moon really; matter of fact, it's all dark."
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q67fzicjzn1.fsf@raytheon.com>
Matthew Danish <·······@andrew.cmu.edu> writes:

> (let ((flag 1))
>   (apply 'fun1 "foo" "bar" (if (oddp flag) '("baz") '("one" "two"))))

Right, use apply. But, to change the problem a little, what if we're
trying to make a similar call, but against an intermediate macro:

(defun fun1 (&rest args)
  (format nil "~{~A~^ ~}" args))

(defmacro not-as-fun (&rest args)
  `(fun1 ,@args))


Now try something like:

(let ((flag 2))
  (not-as-fun "foo" "bar" (if (oddp flag)
                              "baz"
                              '("one" "two"))))


We can't use apply here. Is the answer just, "Don't write a macro like
not-as-fun?"

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: Alan Crowe
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <86ad8jeuqk.fsf@cawtech.freeserve.co.uk>
Steven E. Harris inquired:
     (defun fun1 (&rest args)
       (format nil "~{~A~^ ~}" args))

     (defmacro not-as-fun (&rest args)
       `(fun1 ,@args))

     Now try something like:

     (let ((flag 2))
       (not-as-fun "foo" "bar" (if (oddp flag)
				   "baz"
				   '("one" "two"))))

     We can't use apply here. Is the answer just, "Don't
     write a macro like not-as-fun?"

That's a good question. I've been pondering it with the
help of this little file:

(defparameter *counter* 0)

(define-symbol-macro n (incf *counter*))

(defun fun1 (&rest args)
  (format nil "~{~A~^ ~}" args))

(defmacro mac1 (&rest args)
  `(fun1 ,@args))

(defun fun2 (&rest args)
  (apply #'fun1 (append args args)))

(defmacro mac2 (&rest args)
  `(fun1 ,@args ,@args))

The symbol-macro just saves my fingers from wear and tear
typing (incf *counter*) over and over again.

n => 1
n => 2
(fun1 n n (list n n)) => "3 4 (5 6)"
(mac1 n n (list n n)) => "7 8 (9 10)"
(apply #'fun1 n n (list n n)) => "11 12 13 14"

at this point it is a trifle frustrating that we cannot
apply mac1. After all, it seems clear enough what it should
do. It should take out the brackets and give us 
"15 16 17 18"

What puzzles me is whether that clarity is an illusion,
based on the fact the mac1 doesn't do anything distinctively
macric and might as well have been a function. So I press on.

(fun2 n n (list n n)) => "15 16 (17 18) 15 16 (17 18)"
(mac2 n n (list n n)) => "19 20 (21 22) 23 24 (25 26)"

Unlike fun1 and mac1, fun2 and mac2 behave differently.

(apply #'fun2 n n (list n n)) => "27 28 29 30 27 28 29 30"

takes out the brackets, as before. So presumably we want
(apply #'mac2 n n (list n n))
to evaluate to 
"31 32 33 34 35 36 37 38"

Is this a reasonable aspiration? Apply-for-macros would have
to evaluate (list n n) a little to get the '(n n) to pass to
mac2, but somehow it would have to know when to stop, or
else the n's would turn into '(33 34) and we would end up
with
"31 32 33 34 35 36 33 34"

That kind of fine grained control over turning evaluation on
and off sounds like a job for backquote and comma

(eval `(mac2 n n ,@(list 'n 'n))) => "31 32 33 34 35 36 37 38"

so that is one way of ``applying'' a macro.

But perhaps this path leads to insanity

(eval `(mac2 ,n n ,@(list n 'n))) => "39 41 40 42 39 43 40 44"

Is this the path to higher macrology and super
programmer-productivity, or just a way of writing obfuscated
code? I'm way out of my depth here.

Alan Crowe
From: james anderson
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <3F7C1A68.ED71B98B@setf.de>
what is the goal here? as described, it appears too much like trying to figure
out how to make list behave like append.

as an aid to ones mental stability, it helps to consider that the equivalent to

  (apply function x y z rest)

is

  (macroexpand (list* macro-operator x y z rest))

where the arguments are runtime values and source code forms respectively.

should one need an operator which is both a function and a macro operator,
there are always compiler macros, but it has not yet been made clear that they
are called for in this situation.


Alan Crowe wrote:
> 
> Steven E. Harris inquired:
> ...
>      We can't use apply here. Is the answer just, "Don't
>      write a macro like not-as-fun?"
> 
> That's a good question. I've been pondering it with the
> help of this little file:
> 
> ...
From: Kenny Tilton
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <e4Web.17545$q71.8841@twister.nyc.rr.com>
Steven E. Harris wrote:

> Barry Margolin <··············@level3.com> writes:
> 
> 
>>There's no semantic difference between:
>>
>>(defun fun1 (&rest args) ...)
>>(fun1 ...)
>>
>>and
>>
>>(defun fun2 (args) ...)
>>(fun2 (list ...))
> 
> 
> Let's say that fun1 is defined as
> 
> (defun fun1 (&rest args)
>   (format nil "~{~A~^ ~}" args))
> 
> If I call (fun1 "foo" "bar" "baz"), I get
> 
> "foo bar baz"
> 
> as a "flat" list of concatenated strings. But what if I need to
> compose my argument list at runtime? Consider this attempt:
> 
> (let ((flag 1))
>   (fun1 "foo" "bar" (if (oddp flag)
>                         "baz"
>                         '("one" "two"))))
> 
> That begets "foo bar baz." But if flag is even, we get
> 
> "foo bar (one two)"
> 
> I'd like some way to produce the arguments to elicit
> 
> "foo bar one two"
> 
> Is it possible to flatten such an argument list /before/ it gets
> collected in the foo1 &rest parameter, or is that flattening really
> the job of foo1?
>

I am guessing foo1 was at some point the &rest parameter to fun1. If so, 
yes, the way you are setting things up (fun1 being a function, not a 
macro), fun1 has to deal with the fact that you want to supply a list 
argument in a series of arguments to &rest, since fun1 does not even get 
kicked off until that sublist has been assembled as one element of foo1.

Macros, of course, can look at the source and re-write things before 
they get passed along to a function.

Mind you, I have seen old-timers whip out a bizarre tool known as advice 
and wreak havoc with functions, but more I cannot say. And when I just 
went looking for its doc in ACL, I found it to be deprecated in favor of 
  something called fwrap. I think that is pronounced fWrap. :)

kenny
From: Kaz Kylheku
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <cf333042.0309300813.7454f525@posting.google.com>
Steven E. Harris <········@raytheon.com> wrote in message news:<···············@raytheon.com>...
> ;; Attempt 2 - expand args first
> (defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
>   (port:with-gensyms ("" gcmd gargs)
>     `(let ((,gcmd ,cmd)
>            (,gargs (list ,@args)))
>       (with-cmd-result (,var ,gcmd ,gargs)
>         (progn
>           (trace-cmd ,var ,gcmd ,gargs)
>           ,@body)))))

Evaluate this and adapt the trick to your code:

  `(let (,@(mapcar #'list '(a b c) '(1 2 3))))

MAPCAR can take more than one list and ``zipper'' them through a
function. In your code, this would look like:

  `(let ((,gcmd ,cmd) ,@(mapcar #'list gargs args)) ...)
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q67smmep7md.fsf@raytheon.com>
···@ashi.footprints.net (Kaz Kylheku) writes:

> MAPCAR can take more than one list and ``zipper'' them through a
> function. In your code, this would look like:
>
>   `(let ((,gcmd ,cmd) ,@(mapcar #'list gargs args)) ...)

Here, gargs would need to be a list of gensyms, not a single gensym
like my original attempt. It looks like James Anderson provided a
similar hint, using a small lambda function rather than just using
#'list.

Thanks, I'm off to experiment.

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: james anderson
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <3F79302A.70C33178@setf.de>
you have to work with the source as a thing in itself.

"Steven E. Harris" wrote:
> 
> I'm stuck trying to wrap some functions and macros taking &rest
> parameters, and I can't figure out how to use &rest parameters more
> than once while avoiding multiple evaluation. I'll explain with some
> simplified examples.
> 


(defun execute-cmd (cmd &rest args)
  (format nil "<~A~{ ~A~}>" cmd args))

(defmacro with-cmd-result ((var (cmd &rest args)) &body body)
  `(let ((,var (execute-cmd ,cmd ,@args)))
    ,@body))

(defun trace-cmd (res cmd &rest args)
  (format *trace-output* "cmd: ~A~{ ~A~} => ~A" cmd args res))



(defmacro with-cmd-result-traced ((cmd-result (cmd &rest args)) &body body)
  (let ((cmd-var (gensym "CMD-"))
        (args-vars (mapcar #'(lambda (arg) (declare (ignore arg))
                              (gensym "ARG-"))
                           args)))
    `(let* ((,cmd-var ,cmd)
            ,@(mapcar #'(lambda (arg-var arg) (list arg-var arg))
                      args-vars args)
            (,cmd-result (execute-cmd ,cmd-var ,@args-vars)))
       (progn (trace-cmd ,cmd-result ,cmd-var ,@args-vars)
              ,@body))))


(defparameter *count* 0)

(defun make-some-other-arg ()
  (format nil "MADE_ARG_~d" (incf *count*)))

(with-cmd-result-traced (res ("foo" "bar" (make-some-other-arg)))
  (format nil "result: ~A" res))
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q67wubqp7vj.fsf@raytheon.com>
james anderson <··············@setf.de> writes:

> you have to work with the source as a thing in itself.

I see what you mean below.

[...]

> (defmacro with-cmd-result-traced ((cmd-result (cmd &rest args)) &body body)
>   (let ((cmd-var (gensym "CMD-"))
>         (args-vars (mapcar #'(lambda (arg) (declare (ignore arg))
>                               (gensym "ARG-"))
>                            args)))
>     `(let* ((,cmd-var ,cmd)
>             ,@(mapcar #'(lambda (arg-var arg) (list arg-var arg))
>                       args-vars args)
>             (,cmd-result (execute-cmd ,cmd-var ,@args-vars)))
>        (progn (trace-cmd ,cmd-result ,cmd-var ,@args-vars)
>               ,@body))))

Wow. I was too frustrated yesterday to come to that step-wise
evaluation and rebinding of the &rest argument.

But I noticed that you cheated a little bit: you reimplemented
with-cmd-result inside of with-cmd-result-traced by coping the
(execute-cmd ...) form. What if we couldn't do that, if we had to call
upon the with-cmd-result macro? I'm going to experiment with that now.


> (defparameter *count* 0)
>
> (defun make-some-other-arg ()
>   (format nil "MADE_ARG_~d" (incf *count*)))
>
> (with-cmd-result-traced (res ("foo" "bar" (make-some-other-arg)))
>   (format nil "result: ~A" res))

I had written a nearly identical make-some-other-arg to prove that I
was liable to multiple evaluation. Thanks for validating that
exploratory process.

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q677k3qp3m7.fsf@raytheon.com>
Steven E. Harris <········@raytheon.com> writes:

> What if we couldn't do that, if we had to call upon the
> with-cmd-result macro? I'm going to experiment with that now.

Following up to myself, suggestions by James and Kaz worked out
fine. I was able to call upon the with-cmd-result macro with the
evaluated and rebound &rest parameter copy.

Of course, I'm still doubting if the interface is worth keeping, but
the exploration provides for much-needed learning about the details
mentioned in the subject line. Thanks for all your help.

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: Pascal Bourguignon
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <87u16ubth0.fsf@thalassa.informatimago.com>
Steven E. Harris <········@raytheon.com> writes:
> ;; Attempt 2 - expand args first, then again
> (defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
>   (port:with-gensyms ("" gcmd gargs)
>     `(let ((,gcmd ,cmd)
>            (,gargs (list ,@args)))
>       (with-cmd-result (,var ,gcmd ,@gargs)
>         (progn
>           (trace-cmd ,var ,gcmd ,@gargs)
>           ,@body)))))

Double back-quote is evil. eval is divine.

(defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
  (port:with-gensyms
   ("" gcmd gargs gpgm)
   `(let* ((,gcmd ,cmd)
           (,gargs (list ,@args))
           (,gpgm  (list 'with-cmd-result
                         (cons ',var (cons ,gcmd ,gargs))
                         (cons 'progn
                               (cons
                                (cons 'trace-cmd
                                      (cons ',var
                                            (cons ,gcmd ,gargs)))
                                ',body)))))
      (format t "pgm=~S~%" ,gpgm) ;; for debugging. 
      (eval ,gpgm)))
  )



(with-cmd-result-traced (res "foo" "bar" (make-some-other-arg))
  (format nil "result: ~A" res))

pgm=
(WITH-CMD-RESULT (RES "foo" "bar" "baz")
 (PROGN (TRACE-CMD RES "foo" "bar" "baz") (FORMAT NIL "result: ~A" RES)))
cmd: foo bar baz => foo bar baz
"result: foo bar baz"

-- 
__Pascal_Bourguignon__
http://www.informatimago.com/
Do not adjust your mind, there is a fault in reality.
From: Matthew Danish
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <20030930145426.GC1454@mapcar.org>
On Tue, Sep 30, 2003 at 09:55:55AM +0200, Pascal Bourguignon wrote:
> Double back-quote is evil. eval is divine.

You are joking, right?

-- 
; Matthew Danish <·······@andrew.cmu.edu>
; OpenPGP public key: C24B6010 on keyring.debian.org
; Signed or encrypted mail welcome.
; "There is no dark side of the moon really; matter of fact, it's all dark."
From: Pascal Bourguignon
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <87y8w5a00j.fsf@thalassa.informatimago.com>
Matthew Danish <·······@andrew.cmu.edu> writes:
> On Tue, Sep 30, 2003 at 09:55:55AM +0200, Pascal Bourguignon wrote:
> > Double back-quote is evil. eval is divine.
> 
> You are joking, right?

Not  at  all. As  soon  as you  start  to  think about  "encapsulated"
backquoting, you get problems because  the first coma always refers to
the last back quote.

On  the  other hand,  each  time I  had  heary  macro problems  (macro
generating defmacros,  etc), I could  solve them building  the program
(list) and sending it to eval.

-- 
__Pascal_Bourguignon__
http://www.informatimago.com/
Do not adjust your mind, there is a fault in reality.
From: Rob Warnock
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <NDudnYebK-hjHueiXTWc-g@speakeasy.net>
Pascal Bourguignon  <····@thalassa.informatimago.com> wrote:
+---------------
| Matthew Danish <·······@andrew.cmu.edu> writes:
| > Pascal Bourguignon wrote:
| > > Double back-quote is evil. eval is divine.
| > 
| > You are joking, right?
| 
| Not  at  all. As  soon  as you  start  to  think about  "encapsulated"
| backquoting, you get problems because  the first coma always refers to
| the last back quote.
| 
| On  the  other hand,  each  time I  had  heary  macro problems  (macro
| generating defmacros,  etc), I could  solve them building  the program
| (list) and sending it to eval.
+---------------

Which fails horribly the first time the inner program needs access to
the lexical environment of the macro call...


-Rob

-----
Rob Warnock, PP-ASEL-IA		<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Joe Marshall
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <1xtx11mk.fsf@ccs.neu.edu>
Pascal Bourguignon <····@thalassa.informatimago.com> writes:

> Double back-quote is evil. eval is divine.

Double back-quote just takes a little practice.
The magic is understanding that double unquote
is   

    ,',foo

not 
    ,,foo

as you might think.


Avoid EVAL, though.  It simply isn't necessary and
debugging a macro that expands to a macro isn't going
to be any easier when you attempt to expand the middle
level in a context where the outer level isn't visible.
  
From: Madhu
Subject: eval (Re: macros, &rest parameters, mulitple evaluation, and forwarding)
Date: 
Message-ID: <xfe3ceb69od.fsf_-_@santafe.cs.unm.edu>
Helu
* Joe Marshall <···@ccs.neu.edu> <············@ccs.neu.edu> :
|
...<snip eminently-correct double-backquote stuff>...
|
| Avoid EVAL, though.  It simply isn't necessary and
| debugging a macro that expands to a macro isn't going
| to be any easier when you attempt to expand the middle
| level in a context where the outer level isn't visible.

I understand that EVAL is almost always the incorrect thing to
do. However consider the following hypothetical situation where I have
a class FOO with many slots:

* (defclass foo () (slot1 slot2))

* (defvar *foo* (make-instance 'foo))

Now perhaps I wish to define accessors to the effect of:

;; (define-symbol-macro FOO-SLOT1 (slot-value *foo* 'slot1))
;; (define-symbol-macro FOO-SLOT2 (slot-value *foo* 'slot2))

i.e. 
;; (setf FOO-SLOT1 10) <=> (setf (slot-value *foo* 'SLOT1) 10) etc 

The most natural way I can think of doing this is:

* (loop for slot in '(slot1 slot2)
  for accessor = (intern (concatenate 'string "FOO-" (symbol-name slot)))
  do (eval `(define-symbol-macro ,accessor (slot-value *foo* ',slot))))
  
I cant think of any good reason to avoid EVAL in this case, in favour
of macrology.  Maybe I am missing something? (like an easy defmacro
solution, or is the motivating example somehow invalid?)

Regards
Madhu
From: Matthew Danish
Subject: Re: eval (Re: macros, &rest parameters, mulitple evaluation, and forwarding)
Date: 
Message-ID: <20031002144032.GG1454@mapcar.org>
On Thu, Oct 02, 2003 at 07:39:14AM -0600, Madhu wrote:
> The most natural way I can think of doing this is:
> 
> * (loop for slot in '(slot1 slot2)
>   for accessor = (intern (concatenate 'string "FOO-" (symbol-name slot)))
>   do (eval `(define-symbol-macro ,accessor (slot-value *foo* ',slot))))
>   
> I cant think of any good reason to avoid EVAL in this case, in favour
> of macrology.  Maybe I am missing something? (like an easy defmacro
> solution, or is the motivating example somehow invalid?)

(macrolet ((frob (&rest slots)
             `(progn
               ,@(loop for slot in slots
                       for accessor = (intern (format nil "~A-~A" 'foo slot))
                       collect `(define-symbol-macro ,accessor
                                 (slot-value *foo* ',slot))))))
  (frob slot1 slot2))

-- 
; Matthew Danish <·······@andrew.cmu.edu>
; OpenPGP public key: C24B6010 on keyring.debian.org
; Signed or encrypted mail welcome.
; "There is no dark side of the moon really; matter of fact, it's all dark."
From: Joe Marshall
Subject: Re: eval (Re: macros, &rest parameters, mulitple evaluation, and forwarding)
Date: 
Message-ID: <he2rzl3s.fsf@ccs.neu.edu>
> On Thu, Oct 02, 2003 at 07:39:14AM -0600, Madhu wrote:
>> 
>> * (loop for slot in '(slot1 slot2)
>>   for accessor = (intern (concatenate 'string "FOO-" (symbol-name slot)))
>>   do (eval `(define-symbol-macro ,accessor (slot-value *foo* ',slot))))

Matthew Danish <·······@andrew.cmu.edu> writes:
> (macrolet ((frob (&rest slots)
>              `(progn
>                ,@(loop for slot in slots
>                        for accessor = (intern (format nil "~A-~A" 'foo slot))
>                        collect `(define-symbol-macro ,accessor
>                                  (slot-value *foo* ',slot))))))
>   (frob slot1 slot2))


To point out something that wasn't mentioned (perhaps it is too obvious, but 
I'm good at seeing the obvious...),

Madhu must arrange (by some mechanism) for his code to be evaluated at
compile time, but that is already built in to Matthew Danish's code.
From: Madhu
Subject: Re: eval (Re: macros, &rest parameters, mulitple evaluation, and forwarding)
Date: 
Message-ID: <xfezngj3v73.fsf@santafe.cs.unm.edu>
Helu
* Joe Marshall <···@ccs.neu.edu> <············@ccs.neu.edu> :

|> On Thu, Oct 02, 2003 at 07:39:14AM -0600, Madhu wrote:
|>> 
|>> * (loop for slot in '(slot1 slot2)
|>>   for accessor = (intern (concatenate 'string "FOO-" (symbol-name slot)))
|>>   do (eval `(define-symbol-macro ,accessor (slot-value *foo* ',slot))))
|
| Matthew Danish <·······@andrew.cmu.edu> writes:
|> (macrolet ((frob (&rest slots)
|>              `(progn
|>                ,@(loop for slot in slots
|>                        for accessor = (intern (format nil "~A-~A" 'foo slot))
|>                        collect `(define-symbol-macro ,accessor
|>                                  (slot-value *foo* ',slot))))))
|>   (frob slot1 slot2))
|
|
| To point out something that wasn't mentioned (perhaps it is too obvious, but 
| I'm good at seeing the obvious...),
|
| Madhu must arrange (by some mechanism) for his code to be evaluated at
| compile time, but that is already built in to Matthew Danish's code.

Indeed!

This was what I was missing. And counts as a reason to avoid EVAL in
this case. (and family of cases where the macro expands to a macro
only used at toplevel)

Thanks for bearing with me!
Regards
Madhu :>
From: Eric Marsden
Subject: Re: eval (Re: macros, &rest parameters, mulitple evaluation, and forwarding)
Date: 
Message-ID: <wzismmbekkr.fsf@melbourne.laas.fr>
>>>>> "md" == Matthew Danish <·······@andrew.cmu.edu> writes:

  md> (macrolet ((frob (&rest slots)
  md>              `(progn
  md>                ,@(loop for slot in slots
  md>                        for accessor = (intern (format nil "~A-~A" 'foo slot))
  md>                        collect `(define-symbol-macro ,accessor
  md>                                  (slot-value *foo* ',slot))))))
  md>   (frob slot1 slot2))

this is missing a WITH-STANDARD-IO-SYNTAX around the INTERN (a
frequent bug in CL programs). 

-- 
Eric Marsden                          <URL:http://www.laas.fr/~emarsden/>
From: Pascal Bourguignon
Subject: Re: eval (Re: macros, &rest parameters, mulitple evaluation, and forwarding)
Date: 
Message-ID: <87n0cjjwzu.fsf@thalassa.informatimago.com>
Eric Marsden <········@laas.fr> writes:

> >>>>> "md" == Matthew Danish <·······@andrew.cmu.edu> writes:
> 
>   md> (macrolet ((frob (&rest slots)
>   md>              `(progn
>   md>                ,@(loop for slot in slots
>   md>                        for accessor = (intern (format nil "~A-~A" 'foo slot))
>   md>                        collect `(define-symbol-macro ,accessor
>   md>                                  (slot-value *foo* ',slot))))))
>   md>   (frob slot1 slot2))
> 
> this is missing a WITH-STANDARD-IO-SYNTAX around the INTERN (a
> frequent bug in CL programs). 

But, isn't  the sexp read before  being interpreted?  So  'foo will be
read with whatever syntax exists  in the macrolet environment, and not
the standard-io syntax, won't it?



At least, that's why problems I had with packages lead me to think:

(defun load-pack-x ()
    (load "package-x.lisp")
    (package-x:initialize)
 )

does not work because package-x  does not exist when defun is execute,
even if it will be existing when package-x:initialize will be called.


-- 
__Pascal_Bourguignon__
http://www.informatimago.com/
Do not adjust your mind, there is a fault in reality.
From: Kalle Olavi Niemitalo
Subject: bug triggered by nonstandard I/O syntax (Re: eval)
Date: 
Message-ID: <87oewzh1hx.fsf_-_@Astalo.kon.iki.fi>
Pascal Bourguignon <····@thalassa.informatimago.com> writes:

> But, isn't the sexp read before being interpreted?  So 'foo will be 
> read with whatever syntax exists in the macrolet environment, and not 
> the standard-io syntax, won't it?

That's right.  The problem is that FORMAT "~A" uses the current 
I/O syntax and INTERN doesn't.  For example:

  (with-standard-io-syntax
    (let ((*print-case* :downcase))
      (intern (format nil "~A-~A" 'foo 'slot1))))
  ;; => |foo-slot1|; NIL
From: Pascal Bourguignon
Subject: Re: bug triggered by nonstandard I/O syntax (Re: eval)
Date: 
Message-ID: <87ad8ijwkt.fsf@thalassa.informatimago.com>
Kalle Olavi Niemitalo <···@iki.fi> writes:

> Pascal Bourguignon <····@thalassa.informatimago.com> writes:
> 
> > But, isn't the sexp read before being interpreted?  So 'foo will be
> > read with whatever syntax exists in the macrolet environment, and
> > not the standard-io syntax, won't it?
> 
> That's right.  The problem is that FORMAT "~A" uses the current I/O
> syntax and INTERN doesn't.  For example:
> 
>   (with-standard-io-syntax
>     (let ((*print-case* :downcase))
>       (intern (format nil "~A-~A" 'foo 'slot1))))
>   ;; => |foo-slot1|; NIL


Ok, I see. But let's write it as:

    (intern (with-standard-io-syntax (format nil "~A-~A" 'foo 'slot1)))


-- 
__Pascal_Bourguignon__
http://www.informatimago.com/
Do not adjust your mind, there is a fault in reality.
From: james anderson
Subject: Re: eval (Re: macros, &rest parameters, mulitple evaluation, and  forwarding)
Date: 
Message-ID: <3F7C4436.E1823895@setf.de>
if the references aren't "in the wild", why wouldn't it be better to use
with-slots / symbol macrolet?

when mcl went from object-lisp to clos, i had alot of files which depended on
this sort of reference. more exactly the reference was not FOO-SLOT1, but
simply SLOT on in a method function for FOO. it was as if there were automatic
WITH-SLOTS wrappers for the method bodies. since the definition operator was
DEFOBFUN rather than DEFMETHOD, and the protocol already required that the
"object variables" be declared, it was easy enough to write a clos-based
DEFOBFUN which generated the with-slots wrapper. one could also do the same
sort of thing introspectively providing that the class definition is
available. 

Madhu wrote:
> ...
> 
> I understand that EVAL is almost always the incorrect thing to
> do. However consider the following hypothetical situation where I have
> a class FOO with many slots:
> 
> * (defclass foo () (slot1 slot2))
> 
> * (defvar *foo* (make-instance 'foo))
> 
> Now perhaps I wish to define accessors to the effect of:
> 
> ;; (define-symbol-macro FOO-SLOT1 (slot-value *foo* 'slot1))
> ;; (define-symbol-macro FOO-SLOT2 (slot-value *foo* 'slot2))
> 
> i.e.
> ;; (setf FOO-SLOT1 10) <=> (setf (slot-value *foo* 'SLOT1) 10) etc
> 
> The most natural way I can think of doing this is:
> 
> * (loop for slot in '(slot1 slot2)
>   for accessor = (intern (concatenate 'string "FOO-" (symbol-name slot)))
>   do (eval `(define-symbol-macro ,accessor (slot-value *foo* ',slot))))
> 
> I cant think of any good reason to avoid EVAL in this case, in favour
> of macrology.  Maybe I am missing something? (like an easy defmacro
> solution, or is the motivating example somehow invalid?)

...
From: Pascal Costanza
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <blbeaj$13n4$1@f1node01.rhrz.uni-bonn.de>
Steven E. Harris wrote:
> I'm stuck trying to wrap some functions and macros taking &rest
> parameters, and I can't figure out how to use &rest parameters more
> than once while avoiding multiple evaluation. I'll explain with some
> simplified examples.
> 
> First take this function that does something kind of command-line
> composition and execution:
> 
> (defun execute-cmd (cmd &rest args)
>   (format nil "~A~{ ~A~}" cmd args))
> 
> 
> Now, here's a little wrapper macro to bind the result of command
> execution and use the result within a provided body:
> 
> (defmacro with-cmd-result ((var cmd &rest args) &body body)
>   `(let ((,var (execute-cmd ,cmd ,@args)))
>     ,@body))
> 
> 
> We can call it like this:
> 
> (with-cmd-result (res "foo" "bar" "baz")
>   (format nil "result: ~A" res))
> 
> 
> Fine. Now imagine some companion function for tracing command
> execution:
> 
> (defun trace-cmd (res cmd &rest args)
>   (format *trace-output* "cmd: ~A~{ ~A~} => ~A" cmd args res))
> 
> 
> We'd like to layer it on top of the with-cmd-result macro above like
> this:
> 
> (defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
>   `(with-cmd-result (,var ,cmd ,@args)  ; eval 1
>     (progn
>       (trace-cmd ,var ,cmd ,@args)      ; eval 2
>       ,@body)))

Why don't you do it like this?

(defmethod execute-cmd (cmd &rest args)
   (format nil "~A~{ ~A~}" cmd args))

(defvar *trace-cmd* nil)

(defmethod execute-cmd :around (cmd &rest args)
   (let ((res (call-next-method)))
     (when *trace-cmd*
       (format *trace-output* "cmd: ~A~{ ~A~} => ~A" cmd args res))
     res))

(defmacro with-cmd-result-traced ((var cmd &rest args) &body body)
   `(let ((*trace-cmd* t))
      (with-cmd-result (,var ,cmd ,@args)
        ,@body)))

When you have access to the MOP you can even add and remove the around 
method in order to avoid the performance penalty. (It probably doesn't 
matter much because format is relatively expensive.)


Pascal

-- 
Pascal Costanza               University of Bonn
···············@web.de        Institute of Computer Science III
http://www.pascalcostanza.de  R�merstr. 164, D-53117 Bonn (Germany)
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q671xtyqmtp.fsf@raytheon.com>
Pascal Costanza <········@web.de> writes:

> Why don't you do it like this?

I haven't gotten to understanding how method combinations work yet,
and hadn't seen this as a job for methods since no classes (or even a
class hierarchy) are involved. But your solution is nice, and looks a
lot like what I was trying to achieve (informally) with my macros.

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: Marco Antoniotti
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <3F7AEF7D.7070408@cs.nyu.edu>
Steven E. Harris wrote:
> Pascal Costanza <········@web.de> writes:
> 
> 
>>Why don't you do it like this?
> 
> 
> I haven't gotten to understanding how method combinations work yet,
> and hadn't seen this as a job for methods since no classes (or even a
> class hierarchy) are involved. But your solution is nice, and looks a
> lot like what I was trying to achieve (informally) with my macros.
> 

This is what the separation of classes and methods buys you.

Cheers
--
Marco
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q67smmclw6o.fsf@raytheon.com>
Marco Antoniotti <·······@cs.nyu.edu> writes:

> This is what the separation of classes and methods buys you.

My primitive understanding of methods thus far was analogous to
template functions in C++: one can write a generic version of the
function, and specialize other versions of the function by
constraining the types of some of the arguments.

Here you're using methods independent of this type variance, instead
using them for ordering and composition. Are there other angles from
which to see methods?

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com
From: Pascal Costanza
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <blf36h$12f$1@newsreader2.netcologne.de>
Steven E. Harris wrote:


> Here you're using methods independent of this type variance, instead
> using them for ordering and composition. Are there other angles from
> which to see methods?

Another cool thing in CLOS is that you can specialize on objects, not 
only on types. For example, here is a Fibonacci function written in CLOS 
style.

; methods for the "objects" 0 and 1
(defmethod fib ((x (eql 0)))
   1)

(defmethod fib ((x (eql 1)))
   1)

; a method for all other cases
(defmethod fib (x)
   (+ (fib (- x 1))
      (fib (- x 2))))

This is quite close to the pattern-matching style of functional or logic 
programming languages.

I find the paper at http://doi.acm.org/10.1145/114669.114671 very 
illuminating in that it contrasts the various styles that have 
influenced the design of CLOS.


Pascal
From: Raffael Cavallaro
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <aeb7ff58.0310012123.47f6066b@posting.google.com>
Pascal Costanza <········@web.de> wrote in message news:<············@newsreader2.netcologne.de>...

> Another cool thing in CLOS is that you can specialize on objects, not 
> only on types. For example, here is a Fibonacci function written in CLOS 
> style.
> 
> ; methods for the "objects" 0 and 1
> (defmethod fib ((x (eql 0)))
>    1)
> 
> (defmethod fib ((x (eql 1)))
>    1)
> 
> ; a method for all other cases
> (defmethod fib (x)
>    (+ (fib (- x 1))
>       (fib (- x 2))))
> 
> This is quite close to the pattern-matching style of functional or logic 
> programming languages.

And it's easy to extend this pattern to include memoization:

(defgeneric fib (n))

(defmethod fib ((n (eql 0))) 1)

(defmethod fib ((n (eql 1))) 1)

(defmethod fib ((n integer))
  (let ((result (+ (fib (1- n)) (fib (- n 2)))))
    (defmethod fib ((n (eql n))) result)
    result))
From: Matthias
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <36wd6dggil9.fsf@chagall.ti.uni-mannheim.de>
·······@mediaone.net (Raffael Cavallaro) writes:

> And it's easy to extend this pattern to include memoization:
> 
> (defgeneric fib (n))
> 
> (defmethod fib ((n (eql 0))) 1)
> 
> (defmethod fib ((n (eql 1))) 1)
> 
> (defmethod fib ((n integer))
>   (let ((result (+ (fib (1- n)) (fib (- n 2)))))
>     (defmethod fib ((n (eql n))) result)
>     result))

Nice idea.  Unfortunately, it seems to be inefficient:

===
* (time (fib 100))
Compiling LAMBDA NIL: 
Compiling Top-Level Form: 

Evaluation took:
  15.25 seconds of real time
  6.892578 seconds of user run time
  0.494141 seconds of system run time
  [Run times include 0.88 seconds GC run time]
  22 page faults and
  183232376 bytes consed.
573147844013817084101
===

(using cmucl 18d on Linux).
From: Christophe Rhodes
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <sqbrt0592e.fsf@lambda.jcn.srcf.net>
Matthias <··@spam.pls> writes:

> ·······@mediaone.net (Raffael Cavallaro) writes:
>
>> (defmethod fib ((n integer))
>>   (let ((result (+ (fib (1- n)) (fib (- n 2)))))
>>     (defmethod fib ((n (eql n))) result)
>>     result))
>
> Nice idea.  Unfortunately, it seems to be inefficient:

?!? "inefficient" compared with _what_?  The difference equation
explicit solution?  Yes.  The combinatorial implementation?  Yes.  The
original, unmemoized algorithm?  I don't think so.

* (time (fib 100))
  32.92 seconds of user run time
  200 Mb consed

* (time (unmemoized-fib 30)) ; note, 30.  I know how this scales.
  108.0 seconds of user run time
  270 Mb consed

but the kicker:

* (time (fib 100))
  0.0 seconds of real time
  128 bytes consed

Christophe
-- 
http://www-jcsu.jesus.cam.ac.uk/~csr21/       +44 1223 510 299/+44 7729 383 757
(set-pprint-dispatch 'number (lambda (s o) (declare (special b)) (format s b)))
(defvar b "~&Just another Lisp hacker~%")    (pprint #36rJesusCollegeCambridge)
From: Matthias
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <36w4qysgfba.fsf@chagall.ti.uni-mannheim.de>
Christophe Rhodes <·····@cam.ac.uk> writes:

> Matthias <··@spam.pls> writes:
> > Nice idea.  Unfortunately, it seems to be inefficient:
> 
> ?!? "inefficient" compared with _what_?  The difference equation
> explicit solution?  Yes.  The combinatorial implementation?  Yes.  The
> original, unmemoized algorithm?  I don't think so.

I meant inefficient compared to a 'standard' memoized solution with
hash-tables or arrays.  I had the implementation technique in mind,
not the algorithm.  Sorry for not making this explicit.
From: Ingvar Mattsson
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <87zngjdi1o.fsf@gruk.tech.ensign.ftech.net>
Christophe Rhodes <·····@cam.ac.uk> writes:

> Matthias <··@spam.pls> writes:
> 
> > ·······@mediaone.net (Raffael Cavallaro) writes:
> >
> >> (defmethod fib ((n integer))
> >>   (let ((result (+ (fib (1- n)) (fib (- n 2)))))
> >>     (defmethod fib ((n (eql n))) result)
> >>     result))
> >
> > Nice idea.  Unfortunately, it seems to be inefficient:
> 
> ?!? "inefficient" compared with _what_?  The difference equation
> explicit solution?  Yes.  The combinatorial implementation?  Yes.  The
> original, unmemoized algorithm?  I don't think so.

(defmethod ffib ((n integer))
  (let ((result (+ (ffib (- n 2)) (ffib (1- n)))))
    (defmethod ffib ((n (eql n))) result)
    result))

* (time (fib 100))
Evaluation took:
  32.82 seconds of real time
  25.94 seconds of user run time
  2.28 seconds of system run time
  [Run times include 13.21 seconds GC run time]
  440 page faults and
  246002512 bytes consed.
573147844013817084101

* (time (ffib 100))
Evaluation took:
  2.93 seconds of real time
  2.37 seconds of user run time
  0.13 seconds of system run time
  [Run times include 0.89 seconds GC run time]
  62 page faults and
  28512056 bytes consed.
573147844013817084101

If you descend as deep as possible in the first branch in a memoised
function, as much as possible is generated by a memoised call, rather
than a "full" call.

//Ingvar (micro-optimisations'r'us)
-- 
Q: What do you call a Discworld admin?
A: Chelonius Monk
From: Marco Antoniotti
Subject: WITH-ADDED-METHOD    Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <3F7C6597.5080501@cs.nyu.edu>
Wasn't there a WITH-ADDED-METHOD macro at some point for this sort of 
things?

It isn't in CL ANSI.

Cheers

Marco





Ingvar Mattsson wrote:
> Christophe Rhodes <·····@cam.ac.uk> writes:
> 
> 
>>Matthias <··@spam.pls> writes:
>>
>>
>>>·······@mediaone.net (Raffael Cavallaro) writes:
>>>
>>>
>>>>(defmethod fib ((n integer))
>>>>  (let ((result (+ (fib (1- n)) (fib (- n 2)))))
>>>>    (defmethod fib ((n (eql n))) result)
>>>>    result))
>>>
>>>Nice idea.  Unfortunately, it seems to be inefficient:
>>
>>?!? "inefficient" compared with _what_?  The difference equation
>>explicit solution?  Yes.  The combinatorial implementation?  Yes.  The
>>original, unmemoized algorithm?  I don't think so.
> 
> 
> (defmethod ffib ((n integer))
>   (let ((result (+ (ffib (- n 2)) (ffib (1- n)))))
>     (defmethod ffib ((n (eql n))) result)
>     result))
> 
> * (time (fib 100))
> Evaluation took:
>   32.82 seconds of real time
>   25.94 seconds of user run time
>   2.28 seconds of system run time
>   [Run times include 13.21 seconds GC run time]
>   440 page faults and
>   246002512 bytes consed.
> 573147844013817084101
> 
> * (time (ffib 100))
> Evaluation took:
>   2.93 seconds of real time
>   2.37 seconds of user run time
>   0.13 seconds of system run time
>   [Run times include 0.89 seconds GC run time]
>   62 page faults and
>   28512056 bytes consed.
> 573147844013817084101
> 
> If you descend as deep as possible in the first branch in a memoised
> function, as much as possible is generated by a memoised call, rather
> than a "full" call.
> 
> //Ingvar (micro-optimisations'r'us)
From: Nick Levine
Subject: Re: WITH-ADDED-METHOD    Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <8732fc48.0310030355.199e95e5@posting.google.com>
Marco Antoniotti <·······@cs.nyu.edu> wrote in message news:<················@cs.nyu.edu>...
> Wasn't there a WITH-ADDED-METHOD macro at some point for this sort of 
> things?
> 
> It isn't in CL ANSI.

WITH-ADDED-METHODS (plural)

It was in the original CLOS proposals (see eg CLTL2), but x3j dropped
it from the language. Sigh of relief at Harlequin when that happened,
as nobody had cared to wreck our CLOS by implementing it.

-n
From: Kalle Olavi Niemitalo
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <87vfr7h88m.fsf@Astalo.kon.iki.fi>
Ingvar Mattsson <······@cathouse.bofh.se> writes:

> If you descend as deep as possible in the first branch in a memoised
> function, as much as possible is generated by a memoised call, rather
> than a "full" call.

I see the effect, but I don't understand how it works.

I traced (fib 10) and (ffib 10).  In both cases, the generic
function is called 19 times.  9 of those calls are to the method
specialized on INTEGER (obviously, these are for the integers 2
to 10), and the remaining 10 are to EQL methods.  The calls to
FIB nest deeper than those to FFIB, but I don't see how that
could affect anything.

What am I missing?
From: james anderson
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <3F7BE7E6.EF5DD322@setf.de>
Matthias wrote:
> 
> ·······@mediaone.net (Raffael Cavallaro) writes:
> 
> > ...
> >
> > (defmethod fib ((n integer))
> >   (let ((result (+ (fib (1- n)) (fib (- n 2)))))
> >     (defmethod fib ((n (eql n))) result)
> >     result))
> 
> Nice idea.  Unfortunately, it seems to be inefficient:

it depends on whether or not that is an issue.

? (defmethod fib (x)
  (let ((temp (make-array (1+ x) :initial-element nil)))
    (labels ((fib_ (x)
               (or (aref temp x)
                   (setf (aref temp x)
                         (if (<= x 1) 1
                             (+ (fib_ (- x 1)) (fib_ (- x 2))))))))
      (let ((result (fib_ x)))
        (defmethod fib ((n (eql x))) result)
        result))))
#<STANDARD-METHOD FIB (T)>
? (time (fib 1000))
(FIB 1000) took 7 milliseconds (0.007 seconds) to run.
 58,984 bytes of memory allocated.
70330367711422815821835254877183549770181269836358732742604905087154537118196933579742249494562611733487750449241765991088186363265450223647106012053374121273867339111198139373125598767690091902245245323403501
? (time (fib 1000))
(FIB 1000) took 1 milliseconds (0.001 seconds) to run.
Of that, 1 milliseconds (0.001 seconds) were spent in The Cooperative
Multitasking Experience.
 224 bytes of memory allocated.
70330367711422815821835254877183549770181269836358732742604905087154537118196933579742249494562611733487750449241765991088186363265450223647106012053374121273867339111198139373125598767690091902245245323403501
? (time (fib 1000))
(FIB 1000) took 0 milliseconds (0.000 seconds) to run.
70330367711422815821835254877183549770181269836358732742604905087154537118196933579742249494562611733487750449241765991088186363265450223647106012053374121273867339111198139373125598767690091902245245323403501
? 

mcl 4.3.1 on a ppc/200

> 
> ===
> * (time (fib 100))
> Compiling LAMBDA NIL:
> Compiling Top-Level Form:
> 
> Evaluation took:
>   15.25 seconds of real time
>   6.892578 seconds of user run time
>   0.494141 seconds of system run time
>   [Run times include 0.88 seconds GC run time]
>   22 page faults and
>   183232376 bytes consed.
> 573147844013817084101
> ===
> 
> (using cmucl 18d on Linux).
From: Christophe Turle
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <bljh19$379$1@news.irisa.fr>
Matthias wrote:
> ·······@mediaone.net (Raffael Cavallaro) writes:
> 
> 
>>And it's easy to extend this pattern to include memoization:
>>
>>(defgeneric fib (n))
>>
>>(defmethod fib ((n (eql 0))) 1)
>>
>>(defmethod fib ((n (eql 1))) 1)
>>
>>(defmethod fib ((n integer))
>>  (let ((result (+ (fib (1- n)) (fib (- n 2)))))
>>    (defmethod fib ((n (eql n))) result)
>>    result))
> 
> 
> Nice idea.  Unfortunately, it seems to be inefficient:
> 
> ===
> * (time (fib 100))
> Compiling LAMBDA NIL: 
> Compiling Top-Level Form: 
> 
>   15.25 seconds of real time
>   6.892578 seconds of user run time
>   0.494141 seconds of system run time
>   [Run times include 0.88 seconds GC run time]
>   22 page faults and
>   183232376 bytes consed.
> 573147844013817084101
> ===
> 
> (using cmucl 18d on Linux).

do you try the second time ? on cmucl 18e :

* (time (fib 100)) ; first time

  Evaluation took:
;   8.11 seconds of real time
;   7.18 seconds of user run time
;   0.76 seconds of system run time
;   16,164,248,588 CPU cycles
;   [Run times include 1.56 seconds GC run time]
;   569 page faults and
;   200,455,040 bytes consed.
;
; 573147844013817084101

* (time (fib 100)) ; second time !

; Evaluation took:
;   0.19 seconds of real time
;   0.19 seconds of user run time
;   0.0 seconds of system run time
;   378,174,508 CPU cycles
;   [Run times include 0.05 seconds GC run time]
;   0 page faults and
;   5,179,216 bytes consed.
;
573147844013817084101

it's much better ;)

-------------------------------------

Christophe Turle
'turle ·@" 'wanadoo 'fr
From: Alan Crowe
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <86fzieeinz.fsf@cawtech.freeserve.co.uk>
Steven E. Harris poses hairy macro problem.
> ...and I can't figure out how to use &rest parameters more
> than once while avoiding multiple evaluation.

Here is my attempt to work my way into the problem.
;;;; The essence of the puzzle is that a fun1 and fun2
;;;; are to get called on a parameter list, without
;;;; multiple evaluation of the parameter list

(defmacro try1 (&rest params)
  `(progn (fun1 ,@params)
	  (fun2 ,@params)))

(defun fun1 (&rest list)
  (prin1 (list* 'fun1res list)))


(defun fun2 (&rest list)
  (prin1 (list* 'fun2res list)))

;;;; The problem shows up in (try1 7 8 (princ 9))
;;;; which expands thus
#|
(macroexpand-1 '(try1 1 (princ 2) 3))

(PROGN (FUN1 1 (PRINC 2) 3) (FUN2 1 (PRINC 2) 3))
|#
;;;; with two calls of (princ)

(defmacro try2 (&rest params)
  (let ((param-holder (gensym "param holder")))
    `(let ((,param-holder (list ,@params)))
       (progn
	 (apply #'fun1 ,param-holder)
	 (apply #'fun2 ,param-holder)))))


expands thus
#|
(macroexpand-1 '(try2 1 (princ 2) 3))

(LET ((#:|param holder900| (LIST 1 (PRINC 2) 3)))
  (PROGN (APPLY #'FUN1 #:|param holder900|) (APPLY #'FUN2 #:|param holder900|)))
#|
and evaluates so 
(try2 1 (princ 2) 3)
=>
2(FUN1RES 1 2 3)(FUN2RES 1 2 3)

with just one call of (princ 2).

Hope this helps

Alan Crowe
From: Steven E. Harris
Subject: Re: macros, &rest parameters, mulitple evaluation, and forwarding
Date: 
Message-ID: <q6765jaqmxp.fsf@raytheon.com>
Alan Crowe <····@cawNOtech.freeSPAMserve.co.uk> writes:

> (defmacro try2 (&rest params)
>   (let ((param-holder (gensym "param holder")))
>     `(let ((,param-holder (list ,@params)))
>        (progn
> 	 (apply #'fun1 ,param-holder)
> 	 (apply #'fun2 ,param-holder)))))

But here fun1 and fun2 are /functions/. What if you hand to call on
two /macros/? Then apply won't help.

-- 
Steven E. Harris        :: ········@raytheon.com
Raytheon                :: http://www.raytheon.com