From: Patrick May
Subject: gensym with multiple-value-bind
Date: 
Message-ID: <m27jced3q5.fsf@patrick.intamission.com>
     Is it possible to call gensym in the variable list of
multiple-value-bind?  I'm defining a macro and currently using a
format like this:

(defmacro when-ready (foo &body body)
  (let ((ready-p (gensym)))
    `(multiple-value-bind (,ready-p bar)
      (check-ready-p ,foo)
      (when ,ready-p ,@body))))

I'd like to eliminate the let, but I don't want to capture ready-p.
Is this possible?  As an aside, is it conventional to use the p suffix
for a function that returns more than a simple t or nil?  I don't work
with any other Lisp programmers, so I only pick up idioms from the
usual books and this newsgroup.

     While I'm in the message buffer, what's the general consensus on
anaphoric macros?  I can see the appeal of being able to use bar in
the body I'm passing in, but it feels dangerous and potentially
confusing.

Regards,

Patrick

------------------------------------------------------------------------
S P Engineering, Inc.    | The experts in large scale distributed OO
                         | systems design and implementation.
          ···@spe.com    | (C++, Java, Jini, CORBA, UML)

From: Zach Beane
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <m3fyr2a9bw.fsf@unnamed.xach.com>
Patrick May <···@spe.com> writes:

>      While I'm in the message buffer, what's the general consensus on
> anaphoric macros?  I can see the appeal of being able to use bar in
> the body I'm passing in, but it feels dangerous and potentially
> confusing.

They get my vote for "dangerous and confusing." I'd prefer to see some
explicit binding introduced.

Zach
From: Will Fitzgerald
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <1129430710.838099.102290@z14g2000cwz.googlegroups.com>
It seems to me that your macro is equivalent to:

(defmacro when-ready (foo &body body)
  `(when (check-ready-p ,foo)
     ,@body))

since it is *bar* you ignore.

Many Lisp functions return 'generalized booleans,' where NIL means
false, and any non-NIL value means true. For example, FBOUNDP in at
least one Lisp returns the function a symbol is bound to when true. Of
course, other functions, like POSITION, do a similar thing.

My brief reading of the Hyperspec leads me to believe that a conforming
Common Lisp implementation could return a non-NIL for any function
listed as returning a 'generalized boolean.' For example, (ODDP 3)
could return 3.

GETHASH returns two values because NIL can be a legit hashtable value;
the second value tells you whether the key is in the table.

SUBTYPEP returns two values, too, anticipating Donald Rumsfeld's
ontology of knowing:

(subtypep t1 t2) => true true, a known known
(subtypep t1 t2) => false true, a known unknown
(subtypep t1 t2) => false false, an unknown unknown.

Anyway, I suspect your CHECK-READY-P could be used as a function
returning a generalized boolean function.
From: Patrick May
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <m2u0fhbuwa.fsf@patrick.intamission.com>
"Will Fitzgerald" <···············@gmail.com> writes:
> It seems to me that your macro is equivalent to:
> 
> (defmacro when-ready (foo &body body)
>   `(when (check-ready-p ,foo)
>      ,@body))
> 
> since it is *bar* you ignore.

     Sorry, I ripped out too much context when I stripped down the
actual code to create the example.  In fact, the check-ready-p
function returns three values, the first of which indicates readiness
and the second two of which are set only if the first is t.  The body
will typically use the second two values.

     Is it possible to use gensym somehow in multiple-value-bind?

Thanks,

Patrick

------------------------------------------------------------------------
S P Engineering, Inc.    | The experts in large scale distributed OO
                         | systems design and implementation.
          ···@spe.com    | (C++, Java, Common Lisp, Jini, CORBA, UML)
From: Jeff M.
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <1129477761.103873.75270@g44g2000cwa.googlegroups.com>
I'm pretty sure the answer to your question is no. However, the
with-gensyms macro is very useful for situations like this. While
technically it doesn't get rid of the let, it is much easier on the
eyes (imo).

Also, in Peter's Practical Common Lisp book, he defines a macro
(only-once or once-only, I can't remember) that is very useful as well,
and I've added it to my little "utils.lisp" file:
http://www.gigamonkeys.com/book/macros-defining-your-own.html.

Something else to note is that I don't understand why you say "I don't
want to capture ready-p". You use it. "bar" is what you aren't using.
Was that just a mistype? You wouldn't want to use gensym inside the
multiple-value-bind, because this would generate a new symbol every
single time it was called. If you truly don't care, just use any
variable name and just declare it ignored:

`(multiple-value-bind (ready-p $0)
    (check-ready-p ,foo)
  (declare (ignore $0))
  (when ,ready-p ,@body))

Jeff M.
From: Tayssir John Gabbour
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <1129478570.862220.98240@f14g2000cwb.googlegroups.com>
Jeff M. wrote:
> Something else to note is that I don't understand why you say "I don't
> want to capture ready-p". You use it. "bar" is what you aren't using.
> Was that just a mistype? You wouldn't want to use gensym inside the
> multiple-value-bind, because this would generate a new symbol every
> single time it was called. If you truly don't care, just use any
> variable name and just declare it ignored:
>
> `(multiple-value-bind (ready-p $0)
>     (check-ready-p ,foo)
>   (declare (ignore $0))
>   (when ,ready-p ,@body))
>
> Jeff M.

Incidentally, too bad you probably can't reliably repeat variable names
in DESTRUCTURING-BIND. Here's a discussion about doing this with
lambda-lists:
<··············@vserver.cs.uit.no>
http://groups.google.com/group/comp.lang.lisp/browse_frm/thread/530e40b8f6d6fc82/d59c25a1afeae5b6#d59c25a1afeae5b6

I would like to do:

(destructuring-bind (frobulator -- -- --)
    (...)
  ...)

where --'s are dummy arguments.


Tayssir

--
"Moreover, under existing conditions, private capitalists inevitably
control, directly or indirectly, the main sources of information
(press, radio, education). It is thus extremely difficult, and indeed
in most cases quite impossible, for the individual citizen to come to
objective conclusions and to make intelligent use of his political
rights."
  -- Albert Einstein
  http://www.monthlyreview.org/598einst.htm
From: Tayssir John Gabbour
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <1129484404.642752.231060@g49g2000cwa.googlegroups.com>
Tayssir John Gabbour wrote:
> Jeff M. wrote:
> > Something else to note is that I don't understand why you say "I don't
> > want to capture ready-p". You use it. "bar" is what you aren't using.
> > Was that just a mistype? You wouldn't want to use gensym inside the
> > multiple-value-bind, because this would generate a new symbol every
> > single time it was called. If you truly don't care, just use any
> > variable name and just declare it ignored:
> >
> > `(multiple-value-bind (ready-p $0)
> >     (check-ready-p ,foo)
> >   (declare (ignore $0))
> >   (when ,ready-p ,@body))
> >
> > Jeff M.
>
> Incidentally, too bad you probably can't reliably repeat variable names
> in DESTRUCTURING-BIND. Here's a discussion about doing this with
> lambda-lists:
> <··············@vserver.cs.uit.no>
> http://groups.google.com/group/comp.lang.lisp/browse_frm/thread/530e40b8f6d6fc82/d59c25a1afeae5b6#d59c25a1afeae5b6
>
> I would like to do:
>
> (destructuring-bind (frobulator -- -- --)
>     (...)
>   ...)
>
> where --'s are dummy arguments.

Hmm, replace one of those --'s near the end with a useful param, as
obviously a &rest param could take care of it all in this flawed
example.


Tayssir

--
"Till there be property there can be no government, the very end of
which is to secure wealth, and to defend the rich from the poor."
  -- Adam Smith
From: David Steuber
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <877jcbjzx2.fsf@david-steuber.com>
"Tayssir John Gabbour" <···········@yahoo.com> writes:

> Tayssir John Gabbour wrote:
> >
> > I would like to do:
> >
> > (destructuring-bind (frobulator -- -- --)
> >     (...)
> >   ...)
> >
> > where --'s are dummy arguments.
> 
> Hmm, replace one of those --'s near the end with a useful param, as
> obviously a &rest param could take care of it all in this flawed
> example.

How is the above different from:

(let ((frobulator (car (...))))
  ...)

-- 
http://www.david-steuber.com/
The UnBlog | Lisp on OS X topics for the most part
Click all the links you want.  I'll make more!
From: Kaz Kylheku
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <1129651915.049279.112030@g49g2000cwa.googlegroups.com>
David Steuber wrote:
> "Tayssir John Gabbour" <···········@yahoo.com> writes:
>
> > Tayssir John Gabbour wrote:
> > >
> > > I would like to do:
> > >
> > > (destructuring-bind (frobulator -- -- --)
> > >     (...)
> > >   ...)
> > >
> > > where --'s are dummy arguments.
> >
> > Hmm, replace one of those --'s near the end with a useful param, as
> > obviously a &rest param could take care of it all in this flawed
> > example.
>
> How is the above different from:
>
> (let ((frobulator (car (...))))
>   ...)

The two may be equivalent in some sense, but they express the idea
differently, which is important.

Also, the semantics are different when the list has fewer than four
elements. (CAR NIL) will happily work, but (DB (X) NIL) is erroneous.
From: Alan Crowe
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <86wtkax13w.fsf@cawtech.freeserve.co.uk>
"Tayssir John Gabbour" <···········@yahoo.com> writes:
> > I would like to do:
> >
> > (destructuring-bind (frobulator -- -- --)
> >     (...)
> >   ...)
> >
> > where --'s are dummy arguments.
> 
> Hmm, replace one of those --'s near the end with a useful param, as
> obviously a &rest param could take care of it all in this flawed
> example.

I think it would be fairly easy to write a macro,
select-bind, that walks the tree passed as the first
argument replacing -- by successive gensyms, and adds an
ignore declaration in the right place.

But is the gain greater than the loss?

Lets me try to explain what worries me about the dummy args
idea. Suppose that one is destructing because one is
representing an object with lots of parts as a list.

Using CLOS instead one might write

  (defmacro define-simple-class (name parents &rest slots)
    `(defclass ,name ,parents
       ,(mapcar
         (lambda (slot)
           (list slot
                 :accessor slot
                 :initarg (intern (symbol-name slot)
                                  "KEYWORD")))
         slots)))

  (define-simple-class menu ()
    beef pork chicken lamb mutton salmon sole cod)

  (with-slots (beef salmon)
              (make-instance 'menu
                             :beef 3.4
                             :salmon 4.5)
    (list beef salmon))

=> (3.4 4.5)

Is it easier to write

(select-bind (beef * * * * salmon * *)
             (a list generating form)
  (do stuff))

Perhaps. But look at

   (select-bind (beef * * * salmon * * *) ...

To do this using with-slots requires

   (with-slots (beef (salmon mutton)) ...

My worry is "how do you debug code with this kind of bug?"
To realise that the bug lies in having three *'s instead of
four *'s, so that you are picking up the mutton slot instead
of the salmon slot requires an awareness that select-bind
can be pretty misleading, because it looks like the names
mean something (because you are familiar with with-slots)
but in fact they don't, the meanng is all in the *-counts.

If you harboured that kind of suspicion, you would very
likely decide that select-bind was a fragile way to code and
not use it.

Alan Crowe
Edinburgh
Scotland
From: Patrick May
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <m2psq5belz.fsf@patrick.intamission.com>
"Jeff M." <·······@gmail.com> writes:
> I'm pretty sure the answer to your question is no. However, the
> with-gensyms macro is very useful for situations like this. While
> technically it doesn't get rid of the let, it is much easier on the
> eyes (imo).

     I share your aesthetics.  I'll consider using with-gensyms
instead of let.

> Something else to note is that I don't understand why you say "I
> don't want to capture ready-p". You use it. "bar" is what you aren't
> using.

     I meant that I didn't want to potentially shadow a variable named
ready-p in the calling environment, hence the use of gensym.  My
example allows bar to be used in the body, which is why I asked about
the risks associated with anaphoric macros.

     Thanks for the response.

Regards,

Patrick

------------------------------------------------------------------------
S P Engineering, Inc.    | The experts in large scale distributed OO
                         | systems design and implementation.
          ···@spe.com    | (C++, Java, Jini, CORBA, UML)
From: Kaz Kylheku
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <1129542643.012393.253300@g47g2000cwa.googlegroups.com>
Patrick May wrote:
> "Jeff M." <·······@gmail.com> writes:
> > I'm pretty sure the answer to your question is no. However, the
> > with-gensyms macro is very useful for situations like this. While
> > technically it doesn't get rid of the let, it is much easier on the
> > eyes (imo).
>
>      I share your aesthetics.  I'll consider using with-gensyms
> instead of let.
>
> > Something else to note is that I don't understand why you say "I
> > don't want to capture ready-p". You use it. "bar" is what you aren't
> > using.
>
>      I meant that I didn't want to potentially shadow a variable named
> ready-p in the calling environment, hence the use of gensym.  My
> example allows bar to be used in the body, which is why I asked about
> the risks associated with anaphoric macros.

Lexical capture is okay if it's documented, and serves some legitimate
purpose.

There are standard constructs which do that.

For instance in a LOOP, you can (RETURN) which breaks out the loop.
That shadows any lexical function or macrolet named RETURN. Or, more
precisely CL:RETURN.

If people have a problem with this type of thing, they can define their
own package into which they import only a precise set of the symbols
from the CL package. If you import LOOP, but not RETURN, then (LOOP
(RETURN)) doesn't mean what it usually means; it means (CL:LOOP
(MYPACKAGE:RETURN)).

Packaging is one way to get hygiene without gensyms. Actually if you
want to be close 100% clean, you can't get away without it.

One hygiene issue is that macro expansions rely on the Lisp language
being stable: they are written in Lisp, with the assumption that none
of the language elements being used are shadowed in the environment.

For instance if you write a lexical function called CONS, and then use
macros in its scope, all hell could break loose.

What you can do is banish the redefining, global or local, of any
standard Lisp functions or operators: simply assert that a program
which does that is undefined.

But the power to banish is a weapon that is wielded by the authors of
the language standard; it doesn't extend to ordinary programmers.

All we have is the package system. My macro expansion relies on
MYPACKAGE::MYFUNCTION, which I haven't exported, so that even if you
USE my package inside yours, you won't get my MYFUNCTION symbol in your
package. So if you happen to write a local function called MYFUNCTION,
it will really be YOURPACKAGE::MYFUNCTION, and not capture my macro's
call.

Moreover, instead of gensyms, I can get away with using private symbols
inside my macros. As the author of MYPACKAGE, I can take all the proper
care that I don't shoot myself in the foot with these non-hygienic uses
of a symbol within my own little domain. As far as everyone else, they
have no business using a private symbol of mine as a variable or
function name!

So really, I would argue that Common Lisp hygiene starts with
packaging.

If you are looking to eliminate gensyms, that's one way to go.

And really, what makes gensyms work? It has to do with packaging! They
are uninterned symbols, that's why they can't be captured. It's not
their uniqueness that makes them work. There are lots of situations in
which you could actually re-use the same gensym.

In a macro, you can often get away with something like:

  (let ((var '#:X))
    `(let ((var ,var)) ... ,var ...))

When the macro source code is read, the Lisp reader parses the #:X
syntax and essentially calls GENSYM. That symbol becomes part of the
macro at read time, and so that same symbol is then used in every
single macro expansion instance. It's unique to that macro: it's as if
X was private to a ''package'' that is inside that macro.

Of course, if the macro makes calls to itself, such that it inserts
references to its #:X into a body of forms that are evaluated within
the inner instance of that macro, this won't work. Those references
will be captured by the inner instance. But that's purely an inner
issue for you to worry about as the macro writer. If you avoid doing
such things, then this #:X is perfectly hygienic, even though it's
re-used in every expansion of your macro.

It's privacy, not absolutel uniqueness that makes a gensym work: the
fact that if the identifier #:X is uttered anywhere else in the
program, it doesn't refer to that #:X.

Packaging does the same thing: it ensures that X uttered somewhere in
the program outside of my package doesn't refer to MYPACKAGE::X, but
some other X.

So here is my long-winded answer to your original question: yes! You
can put GENSYM calls into MULTIPLE-VALUE-BIND. Like this, ready?

  `(multiple-value-bind (#1=#:foo bar) (expr)
     (xyzzy #1#)
     ,@forms)

Instead of using LET at macro-expansion time to grab onto a new GENSYM,
and insert that in multiple places, we grab onto a GENSYM created at
read-time using the #N= syntax, and then refer the reader to patch in
that object using #N#. You just have to verify that nested uses of your
macro are okay with the reuse of #:FOO.
From: Patrick May
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <m2ll0stq7d.fsf@patrick.intamission.com>
"Kaz Kylheku" <········@gmail.com> writes:
[ thought provoking material elided ]
> So here is my long-winded answer to your original question: yes! You
> can put GENSYM calls into MULTIPLE-VALUE-BIND. Like this, ready?
> 
>   `(multiple-value-bind (#1=#:foo bar) (expr)
>      (xyzzy #1#)
>      ,@forms)
> 
> Instead of using LET at macro-expansion time to grab onto a new
> GENSYM, and insert that in multiple places, we grab onto a GENSYM
> created at read-time using the #N= syntax, and then refer the reader
> to patch in that object using #N#. You just have to verify that
> nested uses of your macro are okay with the reuse of #:FOO.

     Thanks!  Your reply gives me a lot to ponder so early on a Monday
morning.

Regards,

Patrick

------------------------------------------------------------------------
S P Engineering, Inc.    | The experts in large scale distributed OO
                         | systems design and implementation.
          ···@spe.com    | (C++, Java, Jini, CORBA, UML)
From: Edi Weitz
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <uk6gcwiif.fsf@agharta.de>
On 17 Oct 2005 02:50:43 -0700, "Kaz Kylheku" <········@gmail.com> wrote:

> For instance in a LOOP, you can (RETURN) which breaks out the loop.
> That shadows any lexical function or macrolet named RETURN. Or, more
> precisely CL:RETURN.

I think you're not right here.  First, from my understanding of
11.1.2.1.2 you can't lexically bind CL:RETURN as a function or macro
anyway in conforming programs.  There are some implementations which
won't complain but in that case the lexical function isn't shadowed by
LOOP.  LispWorks:

  CL-USER 1 > (flet ((return (x) (print (list 'foo x))))
                (loop for i below 10 when (oddp i) do (return i)))

  (FOO 1) 
  (FOO 3) 
  (FOO 5) 
  (FOO 7) 
  (FOO 9) 
  NIL

Second, there's the LOOP /keyword/ RETURN but LOOP keywords are
recognized by name (STRING=) not by symbol identity:

  CL-USER 1 > (defpackage my-package)
  #<PACKAGE MY-PACKAGE>

  CL-USER 2 > (loop for i below 10 when (oddp i) my-package::return i)
  1

Cheers,
Edi.

-- 

Lisp is not dead, it just smells funny.

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: Pascal Bourguignon
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <874q7gb7x0.fsf@thalassa.informatimago.com>
"Kaz Kylheku" <········@gmail.com> writes:
> One hygiene issue is that macro expansions rely on the Lisp language
> being stable: they are written in Lisp, with the assumption that none
> of the language elements being used are shadowed in the environment.
>
> For instance if you write a lexical function called CONS, and then use
> macros in its scope, all hell could break loose.

You can always use cl:cons in your macros, if you intend to _define_
them in a package with shadowed symbols.

Note that the symbols refered by a macro are those that were present in
the environment of its definition, not of its use:

(defpackage :my-macro 
  (:use :cl)
  (:export :mm))
(in-package :my-macro)
;; here we know that unqualified CL symbols come from CL
(defmacro mm (x) `(print ,x))

(defpackage :test
  (:use :cl :my-macro)
  (:shadow :print))
(in-package :test)
(defun print (x) (format t "In TEST: ~A = ~A~%" 'x x))
(mm 'smith)

prints:
SMITH
and nothing else.


And the standard prevents you to redefine cl:print.
>

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/
The mighty hunter
Returns with gifts of plump birds,
Your foot just squashed one.
From: Thomas A. Russ
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <ymibr1o2g27.fsf@sevak.isi.edu>
Patrick May <···@spe.com> writes:

>      Is it possible to call gensym in the variable list of
> multiple-value-bind?  I'm defining a macro and currently using a
> format like this:
> 
> (defmacro when-ready (foo &body body)
>   (let ((ready-p (gensym)))
>     `(multiple-value-bind (,ready-p bar)
>       (check-ready-p ,foo)
>       (when ,ready-p ,@body))))
> 
> I'd like to eliminate the let, but I don't want to capture ready-p.
> Is this possible?

Technically, you could call GENSYM in the variable list of
multiple-value bind, but it wouldn't do you any good.  So that means you
can't avoid the LET binding.  I'm not sure why you want to eliminate it,
since it doesn't hurt you at run time.  The LET is only used during
macroexpansion.

The reason you can't put the gensym in the multiple-value-bind variable
list is that you would then not have any reference to the generated
variable.  Since it is not interned, it cannot be accessed by name.
That would mean you couldn't refer to that variable in the body of the
binding form, thus making it not very useful.


>  As an aside, is it conventional to use the p suffix
> for a function that returns more than a simple t or nil?

Well, sure.  But in general, the p suffix is used to designate functions
that perform a test rather than compute a value.  That means that in
most cases, all you care about is whether the result is NIL or not.
You don't generally use the returned value from functions whose names
end in "p" or "-p".   Returning something other than T is just a
shortcut of the function.

-- 
Thomas A. Russ,  USC/Information Sciences Institute
From: Patrick May
Subject: Re: gensym with multiple-value-bind
Date: 
Message-ID: <m2y84r6gfa.fsf@patrick.intamission.com>
···@sevak.isi.edu (Thomas A. Russ) writes:
> > (defmacro when-ready (foo &body body)
> >   (let ((ready-p (gensym)))
> >     `(multiple-value-bind (,ready-p bar)
> >       (check-ready-p ,foo)
> >       (when ,ready-p ,@body))))
> > 
> > I'd like to eliminate the let, but I don't want to capture
> > ready-p.  Is this possible?
> 
> Technically, you could call GENSYM in the variable list of
> multiple-value bind, but it wouldn't do you any good.  So that means
> you can't avoid the LET binding.  I'm not sure why you want to
> eliminate it, since it doesn't hurt you at run time.

     Primarily I wanted to make sure that I wasn't missing something.
If my implementation is reasonably idiomatic, I'm comfortable with it.

> The reason you can't put the gensym in the multiple-value-bind
> variable list is that you would then not have any reference to the
> generated variable.  Since it is not interned, it cannot be accessed
> by name.  That would mean you couldn't refer to that variable in the
> body of the binding form, thus making it not very useful.

     Understood.  It seemed like a not unreasonable thing to want to
do and Lisp usually seems to be very reasonable, so I figured it was a
question worth asking.

     Thanks for the reply.

Regards,

Patrick

------------------------------------------------------------------------
S P Engineering, Inc.    | The experts in large scale distributed OO
                         | systems design and implementation.
          ···@spe.com    | (C++, Java, Jini, CORBA, UML)