From: Rudolf Schlatte
Subject: return-from / defmacro question
Date: 
Message-ID: <7f53ft$vtv@fstgal00.tu-graz.ac.at>
I am having problems with the following code:

(defmacro with-tables (fn)
  (let ((key (gensym))
        (val (gensym)))
    `(maphash #''(lambda (,key ,val)
                  (declare (ignore ,key))
                  (funcall ,fn ,val))
              �*tables*)))

(defun some-tables (fn)
  (with-tables #'(lambda (table)
                   (when (funcall fn table)
                     (return-from with-tables t)))))

[Code "tested" mod typo errors over slow telnet connection]

CLtL2 says that defmacro is enclosed in an implicit block statement, so 
I thought that a macroexpansion of the function body would look similar to

(block with-tables
  (maphash #'(lambda (G1 G2)
               (declare (ignore G1))
               (funcall #'(lambda (table)
                            (when (funcall fn table)
                              (return-from with-tables t)))
                        G2))
           *tables*))

Instead, I get an error saying that "return-from label WITH-TABLES isn't 
visible".  (This is Allegro CL 5.0 Linux poor-student edition.)  Since I
do not even know where to look for information at the moment, I suspect
that I have missed something quite fundamental.  I would be grateful for
any help / explanation / pointers.  [ObDisclaimer: No homework, just
hobby]

Thanks, Rudi

From: Barry Margolin
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <mxoR2.14$oQ5.585@burlma1-snr2>
In article <··········@fstgal00.tu-graz.ac.at>,
Rudolf Schlatte  <········@ist.tu-graz.ac.at> wrote:
>I am having problems with the following code:
>
>(defmacro with-tables (fn)
>  (let ((key (gensym))
>        (val (gensym)))
>    `(maphash #''(lambda (,key ,val)
>                  (declare (ignore ,key))
>                  (funcall ,fn ,val))
>              �*tables*)))
>
>(defun some-tables (fn)
>  (with-tables #'(lambda (table)
>                   (when (funcall fn table)
>                     (return-from with-tables t)))))
>
>[Code "tested" mod typo errors over slow telnet connection]
>
>CLtL2 says that defmacro is enclosed in an implicit block statement, so 
>I thought that a macroexpansion of the function body would look similar to
>
>(block with-tables
>  (maphash #'(lambda (G1 G2)
>               (declare (ignore G1))
>               (funcall #'(lambda (table)
>                            (when (funcall fn table)
>                              (return-from with-tables t)))
>                        G2))
>           *tables*))

The implicit block encloses the body of the macro, *not* its expansion.
I.e. it's equivalent to:

(defmacro with-tables (fn)
  (block with-tables
    (let ((key (gensym))
          (val (gensym)))
      `(maphash #''(lambda (,key ,val)
                    (declare (ignore ,key))
                    (funcall ,fn ,val))
                �*tables*))))

If you want the expansion to contain a named block, you must put it there
explicitly.  I recommend making the block name be a parameter of the macro,
to avoid problems when there are nested WITH-TABLES uses:

(defmacro with-tables (name fn)
  (let ((key (gensym))
        (val (gensym)))
    `(block ,name
       (maphash #'(lambda (,key ,val)
                    (declare (ignore ,key))
                    (funcall ,fn ,val))
                *tables*))))

(defun some-tables (fn)
  (with-tables this-table
    #'(lambda (table)
        (when (funcall fn table)
          (return-from this-table t)))))

I have two additional comments about your code:

1) You had some extraneous quoting, which I've removed in my version.

2) There doesn't seem to be any reason to implement WITH-TABLES as a macro
in the first place, except to get the block name created.  It could be
implemented as an ordinary function, and you could return from the calling
function (or a block you establish explicitly around the call to
WITH-TABLES):

(defun with-tables (fn)
  (maphash #'(lambda (key val)
               (declare (ignore key))
               (funcall fn val))
           *tables*))

(defun some-tables (fn)
  (with-tables #'(lambda (table)
                   (when (funcall fn table)
                     (return-from some-tables t)))))    

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Rudolf Schlatte
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7f5fut$99j@fstgal00.tu-graz.ac.at>
Barry Margolin <······@bbnplanet.com> wrote:
> In article <··········@fstgal00.tu-graz.ac.at>,
> Rudolf Schlatte  <········@ist.tu-graz.ac.at> wrote:
>>I am having problems with the following code:
>>
[... embarassing code deleted ...]

> 1) You had some extraneous quoting, which I've removed in my version.
vi over modem dialup--they somehow crept in.

> 2) There doesn't seem to be any reason to implement WITH-TABLES as a macro
> in the first place, except to get the block name created. [...]
Well, I certainly learned quite something about macro evaluation by
running into that wall... Will follow your suggestion.

Btw, I really appreciate this newsgroup (and Lisp).  Thanks for the
answers!

Rudi
 
From: Chuck Fry
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7f549m$dhk$1@shell5.ba.best.com>
In article <··········@fstgal00.tu-graz.ac.at>,
Rudolf Schlatte  <········@ist.tu-graz.ac.at> wrote:
>I am having problems with the following code:
>
>(defmacro with-tables (fn)
>  (let ((key (gensym))
>        (val (gensym)))
>    `(maphash #''(lambda (,key ,val)
>                  (declare (ignore ,key))
>                  (funcall ,fn ,val))
>              �*tables*)))
>
>(defun some-tables (fn)
>  (with-tables #'(lambda (table)
>                   (when (funcall fn table)
>                     (return-from with-tables t)))))
>
>[Code "tested" mod typo errors over slow telnet connection]
>
>CLtL2 says that defmacro is enclosed in an implicit block statement [...]

Ah, but remember that this BLOCK is part of the macro expander code,
*not* part of the resulting expansion.  Your macro expansion must
explicitly include a BLOCK form for this to work.

 -- Chuck
-- 
	    Chuck Fry -- Jack of all trades, master of none
 ······@chucko.com (text only please)  ········@home.com (MIME enabled)
Lisp bigot, mountain biker, car nut, sometime guitarist and photographer
The addresses above are real.  All spammers will be reported to their ISPs.
From: Thomas A. Russ
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <ymilnftn2yd.fsf@sevak.isi.edu>
Rudolf Schlatte <········@ist.tu-graz.ac.at> writes:

> CLtL2 says that defmacro is enclosed in an implicit block statement, so 
> I thought that a macroexpansion of the function body would look similar to

I believe that this means that the defmacro expansion code is what is
enclosed in an implicit block statement.  It certainly does not mean
that the generated code is enclosed in a block statement.  The expansion
code is whatever your macro produces.

> 
> I am having problems with the following code:
> 
> (defmacro with-tables (fn)
>   (let ((key (gensym))
>         (val (gensym)))
>     `(maphash #''(lambda (,key ,val)
>                   (declare (ignore ,key))
>                   (funcall ,fn ,val))
>               �*tables*)))
> 
> (defun some-tables (fn)
>   (with-tables #'(lambda (table)
>                    (when (funcall fn table)
>                      (return-from with-tables t)))))
> 
> [Code "tested" mod typo errors over slow telnet connection]
> 
> CLtL2 says that defmacro is enclosed in an implicit block statement, so 
> I thought that a macroexpansion of the function body would look similar to

You can easily test things by using the MACROEXPAND function.  It will
show you what the results of expanding your macro will be.

(pprint (macroexpand '(with-tables #'(lambda (table)
                       (when (funcall fn table)
                         (return-from with-tables t))))) )

(MAPHASH #''(LAMBDA (#:G122 #:G123)
              (DECLARE (IGNORE #:G122))
              (FUNCALL #'(LAMBDA (TABLE)
                           (WHEN (FUNCALL FN TABLE)
                             (RETURN-FROM WITH-TABLES T)))
                       #:G123))
         �*TABLES*)

> 
> (block with-tables
>   (maphash ...
>            *tables*))


To get what you want, there are three choices.  

  ONE is to explicitly include the block form in your macro expansion
  code.  This will let your example work, but I don't like to include
  hard-wired names in the macro expansion.  It just seems like it is 
  asking for trouble.  (In this case it will work because the name is
  the same as the macro, but it makes me feel uneasy)

  (defmacro with-tables (fn)
    (let ((key (gensym))
          (val (gensym)))
     `(block with-tables
        (maphash #'(lambda (,key ,val)
                   (declare (ignore ,key))
                   (funcall ,fn ,val))
               �*tables*))))


   TWO is to explicitly include the block outside of where you want
   the macro to appear.  This is slightly more cumbersome, but it
   doesn't require you to know what the block name is that the macro
   establishes.

   (defun some-tables (fn)
     (block HERE
        (with-tables #'(lambda (table)
                         (when (funcall fn table)
                            (return-from HERE t))))))
    
   THREE is to return from the outer function instead:

   (defun some-tables (fn)
     (with-tables #'(lambda (table)
                      (when (funcall fn table)
                        (return-from SOME-TABLES t)))))

> [ObDisclaimer: No homework, just hobby]

I think this was obviously not a homework problem.  It just didn't have
that feel to it.

-- 
Thomas A. Russ,  USC/Information Sciences Institute          ···@isi.edu    
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwyajtihy2.fsf@world.std.com>
···@sevak.isi.edu (Thomas A. Russ) writes:

> Rudolf Schlatte <········@ist.tu-graz.ac.at> writes:
> 
> > CLtL2 says that defmacro is enclosed in an implicit block statement, so 
> > I thought that a macroexpansion of the function body would look similar to
> 
> I believe that this means that the defmacro expansion code is what is
> enclosed in an implicit block statement.  It certainly does not mean
> that the generated code is enclosed in a block statement.  The expansion
> code is whatever your macro produces.

Exactly.

(defmacro foo (x) (return-from foo `',x))         ;<-- good, though overkill

(defmacro bad-foo (x) ;<-- bad unless used in a matching bad-foo block
  `(return-from bad-foo ',x)) 

(defmacro oof (&body forms)  ;<-- ok, but REALLY overkill
  ;; Sample use:  (oof (list 'a 'b)) => (A B)
  ;; Sample use:  (oof (list (oof a) (oof b))) => B
  (return-from oof
    `(block oof
       (macrolet ((oof (x)
                    (return-from oof
                      `(return-from oof ',x))))
         ,@forms))))
From: Erik Naggum
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <3133245123205645@naggum.no>
* Rudolf Schlatte <········@ist.tu-graz.ac.at>
| CLtL2 says that defmacro is enclosed in an implicit block statement ...

  you appear to view macros in a suboptimal way.  a macro is nothing more
  than a function, but it is called by the compiler (or interpreter) and
  its value is used in place of the call.  this is called macro expansion,
  because the macro call is expanded into the value of the called macro.
  in other words, there is no label in scope after returning from a macro
  function any more than there is a label in scope after returning from any
  other function.

  or, fixing another faulty view of macros: there is no magic to its value.
  the value is what you specify it to be and nothing more.

  perhaps this helps, and perhaps not, but I'll make a shot at it:

(defmacro foo (x y z)
  `(list ,x ,y ,z))

  defines a macro that simply makes (foo a b c) turn into (list a b c).
  nothing particularly exciting, but the following might be instructive.
  this is the function that DEFMACRO has constructed.

(pprint (function-lambda-expression (macro-function 'foo)))
=> 
(lambda (excl::**macroarg** excl::..environment..)
  (declare (ignore-if-unused excl::..environment..))
  (excl::dt-macro-argument-check 3 3 excl::**macroarg** :macro)
  (block foo
    (let* ()
      (let* ((#:g142396 (cdr excl::**macroarg**))
             (x (excl::car-fussy #:g142396 'x))
             (y (excl::car-fussy (cdr #:g142396) 'y))
             (z (excl::car-fussy (cdr (cdr #:g142396)) 'z))
             (#:g142397
              (excl::lambdascan-maxargs 0 (cdr (cdr (cdr #:g142396)))
                '(x y z))))
        (declare (ignore-if-unused #:g142397))
        `(list ,x ,y ,z)))))

  when you understand this (or at least appreciates what it does), you
  should be able to understand the macroexpansion of the DEFMACRO form:

(pprint (macroexpand '(defmacro foo (x y z) `(list ,x ,y ,z))))

  good luck!

#:Erik
-- 
environmentalists are much too concerned with planet earth.  their geocentric
attitude prevents them from seeing the greater picture -- lots of planets are
much worse off than earth is.
From: Rudolf Schlatte
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7f7hqb$gsq@fstgal00.tu-graz.ac.at>
Erik Naggum <····@naggum.no> wrote:
>   perhaps this helps, and perhaps not, but I'll make a shot at it:

> (defmacro foo (x y z)
>   `(list ,x ,y ,z))

>   defines a macro that simply makes (foo a b c) turn into (list a b c).
>   nothing particularly exciting, but the following might be instructive.
>   this is the function that DEFMACRO has constructed.

> (pprint (function-lambda-expression (macro-function 'foo)))
> => 
[...]
>   when you understand this (or at least appreciates what it does), you
>   should be able to understand the macroexpansion of the DEFMACRO form:

> (pprint (macroexpand '(defmacro foo (x y z) `(list ,x ,y ,z))))

  Okay, let's see...  Is the following correct?

(defun my-eval-form (form)
  (let ((name (car form))
	(args (cdr form)))
    (if (fboundp name)
	(cond ((macro-function name)
	       (eval (funcall (macro-function name)
			      (magic-pack-args-for-macro args)
			      (magic-get-env))))
	      (t (apply (function name) args)))
      (error "Function ~A not defined" name))))

  I think I've got at least some of the things you wanted to show me.
With this and the other answers I got both in the group and by email, I
have certainly learned more than I anticipated from this simple question.
Thanks.

Rudi
From: Barry Margolin
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <6hKR2.53$oQ5.2623@burlma1-snr2>
In article <··········@fstgal00.tu-graz.ac.at>,
Rudolf Schlatte  <········@fsmtss08.tu-graz.ac.at> wrote:
>  Okay, let's see...  Is the following correct?
>
>(defun my-eval-form (form)
>  (let ((name (car form))
>	(args (cdr form)))
>    (if (fboundp name)
>	(cond ((macro-function name)
>	       (eval (funcall (macro-function name)
>			      (magic-pack-args-for-macro args)
>			      (magic-get-env))))
>	      (t (apply (function name) args)))

Close.  That should be:

              (t (apply (fdefinition name) (mapcar #'my-eval-form args))))

>      (error "Function ~A not defined" name))))

Your function also doesn't handle a form whose car is a lambda expression
rather than a function/macro name, e.g.

((lambda (x) (+ x 3)) 4)

Nor does it handle invocations of special operators (e.g. LET, BLOCK),
since they can't be applied.

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Vassil Nikolov
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7faehm$a0e$1@nnrp1.dejanews.com>
In article <··········@fstgal00.tu-graz.ac.at>,
  Rudolf Schlatte <········@fsmtss08.tu-graz.ac.at> wrote:
(...)
>   Okay, let's see...  Is the following correct?
>
> (defun my-eval-form (form)
>   (let ((name (car form))
> 	(args (cdr form)))
>     (if (fboundp name)
> 	(cond ((macro-function name)
> 	       (eval (funcall (macro-function name)
                ^^^^
Apart from anything else, you maybe need MY-EVAL-FORM here.
(To emphasise that a macro may expand into another macro.)

> 			      (magic-pack-args-for-macro args)
> 			      (magic-get-env))))
> 	      (t (apply (function name) args)))
>       (error "Function ~A not defined" name))))

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <ucsoa0ig3w.fsf@soft.mercury.bc.ca>
Erik Naggum <····@naggum.no> writes:
> 
> a macro is nothing more than a function, but it is called by the
> compiler...

Would it be more accurate to say that "a macro is almost like
function, except that it is called without first evaluating its
arguments, and it is called by the compiler..." ?

The fact that arguments are not evaluated can be important.

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Barry Margolin
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <_lNR2.65$oQ5.2623@burlma1-snr2>
In article <··············@soft.mercury.bc.ca>,
Joachim Achtzehnter  <·······@kraut.bc.ca> wrote:
>Erik Naggum <····@naggum.no> writes:
>> 
>> a macro is nothing more than a function, but it is called by the
>> compiler...
>
>Would it be more accurate to say that "a macro is almost like
>function, except that it is called without first evaluating its
>arguments, and it is called by the compiler..." ?

Not really.  It's called by the compiler, and the argument is the form
containing the invocation.  The DEFMACRO argument list specifies how this
should then be destructured into variables.

>The fact that arguments are not evaluated can be important.

True, but that's implied.

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwk8vcrzku.fsf@world.std.com>
Barry Margolin <······@bbnplanet.com> writes:

> In article <··············@soft.mercury.bc.ca>,
> Joachim Achtzehnter  <·······@kraut.bc.ca> wrote:
>
> >Would it be more accurate to say that "a macro is almost like
> >function, except that it is called without first evaluating its
> >arguments, and it is called by the compiler..." ?
> 
> Not really.  It's called by the compiler, and the argument is the form
> containing the invocation.  The DEFMACRO argument list specifies how this
> should then be destructured into variables.

The way I describe it is this:

 A macro form is not a program at all.  It is an expression that 
 was chosen for syntactic convenience and that is associatd with
 a program (the macro) which knows how to turn the non-program
 (the macro form) into a program (or into another macro form).
 The process of turning the non-program into a program is called
 "macro expansion".
 
It is important to understand that the data the program receives is
not just "evaluated" or "not evaluated" because it's potentially
more complex than that.  For example, consider:

 (defmacro debug-print (x)
   `(progn (print ',x)
	   (prin1 ,x)))

 (setq stuff '(a b c))
 (debug-print stuff)

The point is that you can't say that STUFF either does or doesn't get
evaluated.  In this case, both happens.  That is, the *program* is
really

 (progn (print 'stuff)  ;<-- this use of STUFF is data (a symbol)
        (prin1 stuff))  ;<-- this use of STUFF is program (evaluated)

But in some other cases, the program completely rewrites what you do:

 (defmacro def-frob (name exp) 
   (let ((frob-name (intern (format nil "FROB-~A" name))))
     `(defun ,frob-name () ,exp)))
 (def-frob foo 3)

When this is expanded, you're going to get

 (defun frob-foo () 3)

The question of whether FOO was "evaluated" or "not evaluated" is kind of
weird since FOO was just data going into DEF-FROB, just as STUFF was data
going into the DEBUG-PRINT above.  But in the *program*, not the *macro
form*, the FOO does not appear at all so it is neither evaluated nor
not evaluated.

This formulation (thinking about macros as simply non-programs stuck
among programs which need to be translated to programs) may not work
for everyone, but maybe some people will find it useful.  It is very
close to what actually happens, but the subtleties of how one 
conceptualizes it do matter.
From: Vassil Nikolov
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7fag59$bdf$1@nnrp1.dejanews.com>
In article <···············@world.std.com>,
  Kent M Pitman <······@world.std.com> wrote:
> Barry Margolin <······@bbnplanet.com> writes:
>
> > In article <··············@soft.mercury.bc.ca>,
> > Joachim Achtzehnter  <·······@kraut.bc.ca> wrote:
> >
> > >Would it be more accurate to say that "a macro is almost like
> > >function, except that it is called without first evaluating its
> > >arguments, and it is called by the compiler..." ?
> >
> > Not really.  It's called by the compiler, and the argument is the form
> > containing the invocation.  The DEFMACRO argument list specifies how this
> > should then be destructured into variables.
>
> The way I describe it is this:
>
>  A macro form is not a program at all.  It is an expression that
>  was chosen for syntactic convenience and that is associatd with
>  a program (the macro) which knows how to turn the non-program
>  (the macro form) into a program (or into another macro form).
>  The process of turning the non-program into a program is called
>  "macro expansion".
>
> It is important to understand that the data the program receives is
> not just "evaluated" or "not evaluated" because it's potentially
> more complex than that.
(...)

May I add to this the following extension of the view point: taking
the above as the macro user's view, the macro implementor's view
would be that they produce a (macro expansion) function; this function
operates on programs just like ordinary functions operate on data.

Since Lisp programs are represented by Lisp data, macro expansion
functions are written in Lisp.

Or:

A macro is not _used_ like a function at all, and macros are *not*
functions, not even ones that do not evaluate their arguments.
A macro is _implemented_ by a function, an ordinary function that
expects to receive its arguments evaluated just like any other
function.

To make things easier for the macro writer, the backquote facility
makes possible a `declarative' style for implementing macros---but
there is a function there.

Or:

Consider, on one hand, doing

  ;; (A)
  (defmacro foo (x y z)
    "Do the bar thing on x, y, and z."
    ;; Implementation note: (FOO X Y Z) -> (BAR X Y Z)
    `(bar ,x ,y ,z))

and, on the other hand, doing

  ;; (B1)
  (defun foo-support (x y z)
    "Return a list of four elements, BAR and the values of
its arguments.  In other words, return a Lisp form where the
operator is BAR, and the values of x, y, and z are in the
operands' positions."
    (list 'bar x y z))

and then (B2) telling the Lisp processor,^1 whenever you see a
form F such that (FIRST F) is FOO, apply FOO-SUPPORT to (REST F)
and start over with whatever FOO-SUPPORT returned.

The effect of (A) is essentially (B1) + (B2).  FOO-SUPPORT is
the macro expansion function, and it is an ordinary function.

__________
^1 `Lisp processor' means here `evaluator or compiler, whoever
   happens to be processing the form with the purpose of executing
   it or preparing for execution.'

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: Erik Naggum
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <3133295791676654@naggum.no>
* Joachim Achtzehnter <·······@kraut.bc.ca>
| Would it be more accurate to say that "a macro is almost like
| function, except that it is called without first evaluating its
| arguments, and it is called by the compiler..." ?

  this is even less accurate.  the macro function is actually called with
  the macro form as a constant.  destructuring typically occurs inside the
  macro body.  (think about it: the macro lambda list is much stronger than
  the function lambda list.)

#:Erik
-- 
environmentalists are much too concerned with planet earth.  their geocentric
attitude prevents them from seeing the greater picture -- lots of planets are
much worse off than earth is.
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwpv54umya.fsf@world.std.com>
Erik Naggum <····@naggum.no> writes:

> * Joachim Achtzehnter <·······@kraut.bc.ca>
> | Would it be more accurate to say that "a macro is almost like
> | function, except that it is called without first evaluating its
> | arguments, and it is called by the compiler..." ?
> 
>   this is even less accurate.  the macro function is actually called with
>   the macro form as a constant.  destructuring typically occurs inside the
>   macro body.  (think about it: the macro lambda list is much stronger than
>   the function lambda list.)

Incidentally, it may help to read my historical paper
"Special Forms in Lisp" at
http://world.std.com/~pitman/Papers/Special-Forms.html

It was written in the Maclisp days (for the 1980 Lisp Conference)
but I've added some annotation that allows you to read it with the
necessary historical perspective.  It surveys the issues surrounding
"functions that don't evaluate their arguments" and "macros".

What Erik says here is absolutely true but the one thing I'd add to
it is that the relevant fact is not "what" the macro is called with
but "when" the macro is called.  Macros execute at compile time, not
at runtime.  Their arguments are (as Erik notes) data.  But importantly,
and unlike old-style FEXPRs (like dinosaurs, now gone from the
landscape) macros cannot just "call eval" in order to see the value of
the variable.

In Maclisp (an old-time Lisp for the PDP10, predating Macintoshes):
 (defun foo fexpr (x) x)
 (foo a b c) => (A B C)
was a function that "didn't evaluate its arguments".  Interlisp had
 ((nlambda (x y z) (list x y z)) a b c) => (a b c)
But in both you could do
 (defun foo fexpr (x) (eval x))
 (defvar *something* 3)
 (foo *something*) => 3
If you tried to make a macro that was
 (defmacro foo (x) (list 'quote (eval x)))
and follow it immediately in code with
 (foo *something*)
the problem is that *something* won't be bound until the program loads
into the execution environment and so the macro will blow up.

So macros are about "when".  They run at compile time because the compiler
can't compile them.  The compiler can only compile their expansion.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <ucogkohx3i.fsf@soft.mercury.bc.ca>
Kent M Pitman <······@world.std.com> writes:
> 
>  (defvar *something* 3)
> If you tried to make a macro that was
>  (defmacro foo (x) (list 'quote (eval x)))
> and follow it immediately in code with
>  (foo *something*)
> the problem is that *something* won't be bound until the program loads
> into the execution environment and so the macro will blow up.

Now you have me really confused! I just tried compiling, then loading
the following file into two Lisp implementations (Allegro 3 and
Allegro 5) and neither blew up. Both happily printed the number 3.

(defvar *something* 3)
(defmacro foo (x) (list 'quote (eval x)))
(foo *something*)
(print (foo *something*))

What am I missing here? Are you saying that this may work in some but
not all implementations?

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwwvzchw33.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> Kent M Pitman <······@world.std.com> writes:
> > 
> >  (defvar *something* 3)
> > If you tried to make a macro that was
> >  (defmacro foo (x) (list 'quote (eval x)))
> > and follow it immediately in code with
> >  (foo *something*)
> > the problem is that *something* won't be bound until the program loads
> > into the execution environment and so the macro will blow up.
> 
> Now you have me really confused! I just tried compiling, then loading
> the following file into two Lisp implementations (Allegro 3 and
> Allegro 5) and neither blew up. Both happily printed the number 3.
> 
> (defvar *something* 3)
> (defmacro foo (x) (list 'quote (eval x)))
> (foo *something*)
> (print (foo *something*))
> 
> What am I missing here? Are you saying that this may work in some but
> not all implementations?

It shouldn't work in any conforming implementation.

Probably the implementation isn't a problem, though since most get it right.
I seriously doubt Allegro has this bug--I just tried it in Allegro 5.0
and it blew up exactly as I'd expected.  (No, I didn't try it before sending
the post, so I'm relieved to see I wasn't wrong.)

 Mapping D:\Program Files\Franz\acl50\lisp.dxl...done.
 Mapping D:\Program Files\Franz\acl50\acl503.epll.
 Allegro CL Enterprise Edition 5.0 [Windows/x86] (8/29/98 10:36)
 Copyright (C) 1985-1998, Franz Inc., Berkeley, CA, USA.  All Rights Reserved.
 ;; Optimization settings: safety 1, space 1, speed 1, debug 2.
 ;; For a complete description of all compiler switches given the
 ;; current optimization settings evaluate (EXPLAIN-COMPILER-SETTINGS).
 USER(1): (compile-file "testme.lisp")
 ;;; Compiling file testme.lisp
 ; While compiling (:TOP-LEVEL-FORM "testme.lisp" 71):
 Error: Attempt to take the value of the unbound variable `*SOMETHING*'.
   [condition type: UNBOUND-VARIABLE]

 Restart actions (select using :continue):
  0: Try evaluating *SOMETHING* again.

Almost surely the problem is that you had previously done
(defvar *something* 3)
and then you compiled this in an environment where *something*
was bound.  The compiler doesn't get a separate compilation environment
from the environment that calls the compiler in most (well, probably all)
lisp implementations (though CL permits it to if it can).  In general, if
you have a file testme.lisp containing:

 (defvar *something* 3)
 (defmacro foo (x) (list 'quote (eval x)))
 (foo *something*)
 (print (foo *something*))

and you do 

 (compile-file "testme.lisp")

you will end up in the debugger.  But if you instead do:

 (defvar *something* 3)
 (compile-file "testme.lisp")

you will only accidentally win because you are using the compile-time
value of *something* instead of the runtime value.  You can get confused
about compile time vs runtime if you're not careful.  If you want a clean
compilation, always do it in a fresh image--at least while you're learning.
It's very easy to pollute your environment if you don't know what you're
doing.  That "pollution" can also be good if you know what's going on.
'Wanted pollution" would be called "customization".

For example, if you do:

 (load "testme.lisp") ;load the interpreted version
 (load (compile-file "testme.lisp")) ;compile and load 

it will work because loading the interpreted version will leave *something*
defined and the compile-file command will be executed in an environment
where the defvar has been seen already.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <m2yajrel05.fsf@wizard.kraut.bc.ca>
Kent M Pitman <······@world.std.com> writes:
> 
> Almost surely the problem is that you had previously done
> (defvar *something* 3)
> and then you compiled this in an environment where *something*
> was bound.

Actually, I had probably done something similar to the following:

> For example, if you do:
> 
>  (load "testme.lisp") ;load the interpreted version
>  (load (compile-file "testme.lisp")) ;compile and load 
> 
> it will work because loading the interpreted version will leave
> *something* defined and the compile-file command will be executed
> in an environment where the defvar has been seen already.

This is an amazingly timely discussion because I had written a couple
of macros which called eval on one of their arguments just a few days
ago. Thanks, for the education! It seems, however, that I may be ok in
this particular case because these macros are only called at runtime
to generate functions based on meta data stored in a database. There
are no calls to these macros in the source files that are being
compiled. Is it acceptable to call eval on macro arguments in that
case?

Joachim
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwk8vbl5op.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> This is an amazingly timely discussion because I had written a couple
> of macros which called eval on one of their arguments just a few days
> ago. Thanks, for the education! It seems, however, that I may be ok in
> this particular case because these macros are only called at runtime
> to generate functions based on meta data stored in a database. There
> are no calls to these macros in the source files that are being
> compiled. Is it acceptable to call eval on macro arguments in that
> case?

Macros that are "only called at runtime" are not really macros.
It really is bad form to do this.

Can you offer a simple example so we can try to propose a clean
alternative?

One other good rule of thumb for macros is this:

  Any place you're tempted to call EVAL in a macro, just take the
  code in question and put it into the result unquoted.

For example:

  (defmacro bad-let1 ((var init) &body forms) ;<--BAD
    `(let ((,var ',(eval init)))
       ,@forms))

  (defmacro good-let1 ((var init) &body forms) ;<--GOOD
    `(let ((,var ,init))
       ,@forms))

Of course, this means the init will get executed every time the form
is evaluated instead of one, but the point is that at macro expansion
time you have to be very careful about what you eval, even when you're
in the runtime part of code.  Consider:

 (defun frob (x)
   (bad-let1 (y x) (print y)))

This isn't going to "work" because (eval 'x) done by the BAD-LET1
macro won't see the lexical binding of X in FROB lambda list.
But if you use the same with GOOD-LET1, it will work because
rather than do an EVAL, you expand into something that will get
evaluated naturally in the right lexical environment.

There are other techniques as well, but which might be applicable to
your situation depends a lot on the details of your situation.  So an
example will help.
From: Erik Naggum
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <3133348161977201@naggum.no>
* Kent M Pitman <······@world.std.com>
| For example:
| 
|   (defmacro bad-let1 ((var init) &body forms) ;<--BAD
|     `(let ((,var ',(eval init)))
|        ,@forms))
| 
|   (defmacro good-let1 ((var init) &body forms) ;<--GOOD
|     `(let ((,var ,init))
|        ,@forms))
| 
| Of course, this means the init will get executed every time the form
| is evaluated instead of one, ...

  if this is important, LOAD-TIME-VALUE would take care of that.  (hm,
  another problematic issue LOAD-TIME-VALUE solves elegantly.  it really
  is quite the neat new special operator.  :)

#:Erik
-- 
environmentalists are much too concerned with planet earth.  their geocentric
attitude prevents them from seeing the greater picture -- lots of planets are
much worse off than earth is.
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfw4smfnvyt.fsf@world.std.com>
Erik Naggum <····@naggum.no> writes:

> * Kent M Pitman <······@world.std.com>
> | For example:
> | 
> |   (defmacro bad-let1 ((var init) &body forms) ;<--BAD
> |     `(let ((,var ',(eval init)))
> |        ,@forms))
> | 
> |   (defmacro good-let1 ((var init) &body forms) ;<--GOOD
> |     `(let ((,var ,init))
> |        ,@forms))
> | 
> | Of course, this means the init will get executed every time the form
> | is evaluated instead of one, ...
> 
>   if this is important, LOAD-TIME-VALUE would take care of that.  (hm,
>   another problematic issue LOAD-TIME-VALUE solves elegantly.  it really
>   is quite the neat new special operator.  :)

Good catch.

I wasn't too worried about it because most times this comes up, a
simple DEFVAR would work so you don't use LET-style technology in the
first place, but yes, if it happens in ways that you can't plan for
with DEFVAR, LOAD-TIME-VALUE is able to be an anonymous version of
same.

I don't tend to reach for LOAD-TIME-VALUE except where I'm otherwise
wedged because I got all my intuitions long before it was available,
but that's probably just me getting old and stuck in my ways.  Best
that new programmers learn all the tricks from the start so they don't
have such historical biases...
From: David Bakhash
Subject: load-time-value
Date: 
Message-ID: <cxj7lrapxnb.fsf_-_@acs5.bu.edu>
I read the examples in the HS, but I can't seem to figure out when this would
be useful.  Would someone explain how this can be useful?  a really useful
thing would be to show how to accomplish what load-time-value does given the
rest of Lisp (e.g. eval-when, etc.)

thanks,
dave
From: Kent M Pitman
Subject: Re: load-time-value
Date: 
Message-ID: <sfwlnfq8ttl.fsf@world.std.com>
David Bakhash <·····@bu.edu> writes:

> I read the examples in the HS, but I can't seem to figure out when this would
> be useful.  Would someone explain how this can be useful?  a really useful
> thing would be to show how to accomplish what load-time-value does given the
> rest of Lisp (e.g. eval-when, etc.)

well, normally i would recommend just knowing it's available and just
using it if the need comes up because it's mostly very rare that you
need it and i'm not sure it's something you want to rush out looking
for reasons to use.

but the cases are all cases where there is a computation that can only
be done at runtime (not compile time) because some value is not yet
available at compile time, and where you don't want to keep doing it
on every time you meet that code.  often a defvar will suffice but if
it's in the case of a macro such that each reference to the macro
needs the info, a load-time-value can be better.

here's one example from an earlier post of mine (april 1 of this year, in the
"Constants and DEFCONSTANT" thread).

(defparameter +lexical-unbound+ (make-symbol "UNBOUND"))

(defun lexical-cell (x)
  (or (get x 'lexical-cell)
      (setf (get x 'lexical-cell) (cons x +lexical-unbound+))))

(defmacro lexical-ref (x) 
  `(cdr (load-time-value (lexical-cell ',x))))

(defmacro deflexical (var value)
  `(progn (define-symbol-macro ,var (lexical-ref ,var))
          (setq ,var ,value)
          ',var))



probably a dejanews search for load-time-value would find others.  
 http://www.dejanews.com/home_ps.shtml
From: Vassil Nikolov
Subject: Re: load-time-value
Date: 
Message-ID: <7fbucg$gel$1@nnrp1.dejanews.com>
In article <···············@world.std.com>,
  Kent M Pitman <······@world.std.com> wrote:
(...)
> but the cases are all cases where there is a computation that can only
> be done at runtime (not compile time) because some value is not yet
             ^^^^^^^
> available at compile time
(...)

load time?

To me, run time proper is later than load time (which is later than
compile time).  This is hard to define rigourously, of course, but
I mean that loading a compiled file that contains (DEFUN FOO ...)
(in compiled form) is load time and then calling FOO is run time.
(If FOO is the `main' function, normally one does not place a call
to FOO in the file to be loaded, though this is not forbidden.)

I feel like opening yet another can of worms, but it is important
to distinguish between

  (defun make-foos (n)
    "Return a list of FOO's; print one when loading."
    (do ((i 0 (+ i 1))
         (l '() (cons (load-time-value (print 'foo)) l)))
        ((= i n) l)))

and

  (defun make-foos (n)
    "Return a list of FOO's that get printed as well."
    (do ((i 0 (+ i 1))
         (l '() (cons (print 'foo) l)))
        ((= i n) l)))

(Untested at post time, sorry.)

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: Kent M Pitman
Subject: Re: load-time-value
Date: 
Message-ID: <sfw3e1yyrwq.fsf@world.std.com>
Vassil Nikolov <········@poboxes.com> writes:

> > but the cases are all cases where there is a computation that can only
> > be done at runtime (not compile time) because some value is not yet
>              ^^^^^^^
> > available at compile time [...]
> 
> load time?
> 
> To me, run time proper is later than load time (which is later than
> compile time).

Sorry, I was being sloppy.

> I feel like opening yet another can of worms, but it is important
> to distinguish between [example of runtime vs load-time].

This is a good distinction which I certainly make as well.
I was really talking less about "times" and more about "environments".
The compile time and runtime environments are conceptually different;
the runtime and loadtime environment are different only in the sense
that a cons is different before and after you rplacd it; change of state,
not change of identity.  That's not to say they're not different, though,
and I should have been more careful in my terminology.

I believe the failure to teach "times" (in the eval-when sense) is one
of the most obvious gaps in computer science textbooks.  Some
languages give you access to more than others do, but they are always
relevant in all languages--in some languages only becuase you can tell
that the reason that programs don't work is that the language failed
to give you access to the right "time".  Lisp isn't perfect
either--absence of access to finalization time in Lisp was recently
noted on this newsgroup as another.

There are a few other obvious things like this which I hope to include
in my book.
From: Joachim Achtzehnter
Subject: Re: load-time-value
Date: 
Message-ID: <ucn2045xr9.fsf@soft.mercury.bc.ca>
Kent M Pitman <······@world.std.com> writes:
> 
> I believe the failure to teach "times" (in the eval-when sense) is
> one of the most obvious gaps in computer science textbooks.

You are probably right, more emphasis on this topic in textbooks may
help. However, I think the language definition itself is partly to
blame as well. I say this because, in practise, people often learn by
experimentation. In this case, the language is defined in a way that
certain code always works when used in an interpretive working
environment (where experimentation tends to occur), and is guaranteed
to fail when the same code is independently compiled. True, in the end
the language definition is the judge, and the code is invalid, or at
least problematic. But a programming language is not an end in itself,
confusing users should be avided when possible.

Could the semantics of macros have been defined differently to avoid
this problem? For example, would it be possible for the compiler to
detect problematic situations and then postpone macro expansion to
loadtime or runtime? After all, the expander function is available at
runtime. Or alternatively, if that is not desirable or not possible,
could the semantics have been defined such that failures occur in an
interpretive working environment as well?

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Kent M Pitman
Subject: Re: load-time-value
Date: 
Message-ID: <sfw676sbcz7.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> Could the semantics of macros have been defined differently to avoid
> this problem? For example, would it be possible for the compiler to
> detect problematic situations and then postpone macro expansion to
> loadtime or runtime?

I don't see how.  You get to run a Turing machine to do the expansion.
The halting problem would forbid any definition that put the compiler
in the position of doing this deterministically; further, a definition
that was not deterministic would not be acceptable.

> After all, the expander function is available at
> runtime. 

Well, it's not necessarily.  That depends on whether the system loads it.
If the DEFMACRO form is loaded, then indeed it will be available.
(In early Maclisp, that didn't used to be true, even if the self-same file
was loaded.)  But since the compiler is required to remove all macro
references, unless LOAD or EVAL or COMPILE-FILE will be called at runtime,
there is no point to having the macros avialable at runtime, and because
the loading of that environment is user-directed, the compiler can't
rely on macro definitions being available.

> Or alternatively, if that is not desirable or not possible,
> could the semantics have been defined such that failures occur in an
> interpretive working environment as well?

The interpreter/compiler distinction isn't relevant, so I'm not sure
what you mean here.  

The thing I *think* you're getting confused about is the notion that
the compiler environment is not in a seprate address space even when
called from the runtime of other programs.  That's not really the
"interpreted environment"--that's someone else's runtime.  Anyway, the
only way to assure separation is to spawn a separate process with a
new address space, as KCL did and perhaps some of its descendant
implementations (gnu cl?) do.  However, the lisp machine couldn't do
this because the lisp machine didn't get a new address space when it
spawned new processes.  The definition absolutely had to work for lisp
machines.  Further, there is great power that comes from being able to
pun these two things, so it's not all 100% obvious you want this
separation.  The real problem happens not just in macros themselves
but in things that the macro stores into the heap.  If a macro does
(setf (get 'x 'y) something), the problem is that the symbol X is
going to be shared between the compiler and the runtime system calling
it, and so any attempt by the compiler to maintain separate lexical
environments for variables will fall apart by stores into the heap in
ways that are associated with symbols or the file system or other
external landmarks.  So since it didn't work to separate these, the
language just doesn't try very hard.
From: Joachim Achtzehnter
Subject: Re: load-time-value
Date: 
Message-ID: <ucn204z5is.fsf@soft.mercury.bc.ca>
Kent M Pitman <······@world.std.com> writes:
>
> Joachim Achtzehnter <·······@kraut.bc.ca> writes:
> 
> > Or alternatively, if that is not desirable or not possible,
> > could the semantics have been defined such that failures occur
> > in an interpretive working environment as well?
> 
> The interpreter/compiler distinction isn't relevant, so I'm not
> sure what you mean here.

Have to admit that my understanding of the foundations is not (yet)
very deep. So, if you say the inconsistent (from my perspective)
behaviour cannot be avoided, I'll have to take your word for it.

What I meant was demonstrated by the simple example you posted
earlier. I loaded the Lisp source file and things worked without
error. But attempting to compile without first loading the source file
resulted in an error. I may be using totally the wrong words to
describe the differences, but naively this looks as if compiled code
somehow has different semantics from interpreted code, while (naive)
users like me may expect only a difference in performance.

> The thing I *think* you're getting confused about is the notion that
> the compiler environment is not in a seprate address space even when
> called from the runtime of other programs.

Don't think that is what I'm getting at. I do understand your
explanations about environments, at least to some degree, and I accept
that the outcome of (compile-file "foo.lisp") may depend on what
happened before, i.e. depends on the environment from which the
compiler was called. What I find less acceptable is that (load
"foo.lisp") on the one hand, and (compile-file "foo.lisp") followed by
(load "foo.fasl") are not equivalent.

Presumably, the different behaviour occurs because (load "foo.lisp")
interleaves interpreting of the file's contents with loading and
running, (compile-file "foo.lisp") on the other hand only interprets,
or rather compiles, the contents without incrementally modifying the
environment, or at least without running anything. Probably, one
doesn't want compile-file to run anything, but how about making
loading of source files behave more like compile-file followed by
loading of the compiled file?

This still wouldn't help in situations where expressions are typed one
by one at the toplevel loop. So perhaps, this is what you are trying
to say? The environment for both interpretation and compilation would
have to be separated from the runtime environment.

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Kent M Pitman
Subject: Re: load-time-value
Date: 
Message-ID: <sfwlnfo1akp.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> this looks as if compiled code
> somehow has different semantics from interpreted code, while (naive)
> users like me may expect only a difference in performance.

I think it's not about that, though I didn't go back and dredge back up
your test case so might be misremembering.

If you had loaded the compiled file first (before compiling it) you
would have still avoided the error.  That's just harder to set up.
It's loading something first (before compiling) that matters, so you
have to bootstrap it by first having something uncompiled since it's
the same file you're compiling and it can't initially be compiled
(that's not a property of interpreted or compiled code, it's just a
property of the universe).  so you could have made the same bug (non-error
where error expected) happen with

 Image 1 | (load "foo.lisp")
 Image 1 | (compile-file "foo.lisp")

 Image 2 | (load "foo.fasl") ;or .wfasl or whatever your lisp uses
 Image 2 | (compile-file "foo.lisp")

Therefore, the thing doesn't have to do with interpreted vs compiled.
It has to do with show-through of the environment into which you've
loaded other code into the environment doing the compile-file.
That show-through is not required, but it is permitted, and it's
there in most implementations.

Another cue that it's not a compiled/interpreted issue is that
some implementations (like MCL) implement EVAL as [effectively]
 (defun eval (x) (funcall (compile nil `(lambda () ,x))))
and since this same issue would come up in MCL, it's not a
compiled-interpreted issue.

All of that said, though, I think some of your other remarks below
are quite relevant.


> Presumably, the different behaviour occurs because (load "foo.lisp")
> interleaves interpreting of the file's contents with loading and
> running, (compile-file "foo.lisp") on the other hand only interprets,
> or rather compiles, the contents without incrementally modifying the
> environment, or at least without running anything.

This is also in play, yes.  Good of you to notice it.  These effects are
often subtle but are quite important.  The fact that you were able to
bootstrap the problem with a single file does rely on this a bit.

> Probably, one
> doesn't want compile-file to run anything, but how about making
> loading of source files behave more like compile-file followed by
> loading of the compiled file?

This has been discussed in some language design arenas, though I think
not X3J13/CL.  It is a quite sane suggestion and one I have some
sympathy for.  A large number of semantic weirdnesses in CL can be
accounted for by the failure to do this--it provides some additional
power to allow the present behavior, but at great cost.  The largest
example of cost is that the failure to do this makes writing a 
CL cross-compiler very hard (if not impossible).  [People have marketed
cross-compilers, so I could be wrong on this point, but my impression has
always been that the cross-compilers had some caveats about how you had
to structure your files to avoid the subtle issues you raise here.]

> This still wouldn't help in situations where expressions are typed one
> by one at the toplevel loop. So perhaps, this is what you are trying
> to say? The environment for both interpretation and compilation would
> have to be separated from the runtime environment.

Lisp is heavily designed around the idea of interactive testing, and
I'm sure it's that tradition that led to the idea that a file is
basically like a script for an interactive session.

You ask some good questions.
From: Vassil Nikolov
Subject: Re: load-time-value
Date: 
Message-ID: <7fh212$pt5$1@nnrp1.dejanews.com>
In article <··············@soft.mercury.bc.ca>,
  Joachim Achtzehnter <·······@kraut.bc.ca> wrote:
> Kent M Pitman <······@world.std.com> writes:
> >
(...)
> I loaded the Lisp source file and things worked without
> error. But attempting to compile without first loading the source file
> resulted in an error.
(...)
> What I find less acceptable is that (load
> "foo.lisp") on the one hand, and (compile-file "foo.lisp") followed by
> (load "foo.fasl") are not equivalent.
>
> Presumably, the different behaviour occurs because (load "foo.lisp")
> interleaves interpreting of the file's contents with loading and
> running, (compile-file "foo.lisp") on the other hand only interprets,
> or rather compiles, the contents without incrementally modifying the
> environment, or at least without running anything. Probably, one
> doesn't want compile-file to run anything, but how about making
> loading of source files behave more like compile-file followed by
> loading of the compiled file?

May I complement Kent Pitman's reply (which, by the way, also helped
me understand that DEFVAR/DECLAIM issue better) with the following.

In the simplest case, e.g. only DEFUNs in the source file, there is
no problem in compiling the file without loading it first.  In more
complicated cases Lisp itself provides only partial support, e.g.
the file compiler notes each DEFMACRO it sees so that it can later
compile correctly macro calls of macros defined earlier in the same
file.  The rest of the support, if necessary, must be provided
by the programmer, for example wrapping readtable setup in EVAL-WHEN.
If, as another example, DEFMACROs are at the bottom of the file
(whether this is good practice is another matter), then the simplest
thing to do is to LOAD and then COMPILE-FILE.  (And it is better to
move the DEFMACROs in a different file, if it is undesirable to
have them early in the file, and ensure it is loaded.)  A more
hairy example would be `mutually recursive macros.'

So one sometimes does want COMPILE-FILE to run something, though
not everything indiscriminately.

So it is not that interpreted and compiled code have different
semantics; it is just that they may, in more complicated cases,
require different preparation.  Often one does not notice,
because one has already evaluated all the stuff in the file (e.g.
from within the editor); often the preparation is something
specific, but just goes ahead and loads the whole file, since
there usually is no harm in executing the rest of it.

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: Howard R. Stearns
Subject: Re: load-time-value
Date: 
Message-ID: <371CCC66.297E948E@elwood.com>
Vassil Nikolov wrote:
> ...
>  The rest of the support, if necessary, must be provided
> by the programmer, for example wrapping readtable setup in EVAL-WHEN.
>...

You're right, but lets make sure no one gets confused by what happens at
read time versus compile time.  Wrapping readtable setup in (eval-when
(:compile-toplevel) ...) may or may not help compile-file properly read
forms which depend on this setup.

The spec says "Successive forms are read from the file by compile-file
and processed..."  My intereptation of this is that each top level form
is read completely and then processed before the next top level form is
read.  However:

 1. Others might not agree.

 2. Others might agree, yet still choose to write their compiler
differently.  I.e., they might read the whole file first before doing
anything that might allow eval-when :compile-toplevel.  Just because *I*
think that's non-conforming doesn't mean that everyone will feel that
they are compelled to comply.  I think there are some very good reasons
for choosing to implement compile-file that way, and I can't fault
anyone for doing so.

 3. If you wrap the readtable setup in the proper eval-when and have the
whole thing appear at top level, the best you can hope to do is have
remaining TOP-LEVEL forms read correctly.

 4. There are other issues that aren't about read time vs. compile time,
but that's another story.  (1. If you side effect the readtable and the
readtable is the same one used by your top-level, then you are side
effecting it and subsequent compilations as well.  2. On the other hand,
there is no way to permanently set the *readtable* variable from within
a source file.)
From: Kent M Pitman
Subject: Re: load-time-value
Date: 
Message-ID: <sfwyajmhcuf.fsf@world.std.com>
"Howard R. Stearns" <······@elwood.com> writes:

> 
> Vassil Nikolov wrote:
> > ...
> >  The rest of the support, if necessary, must be provided
> > by the programmer, for example wrapping readtable setup in EVAL-WHEN.
> >...
> 
> You're right, but lets make sure no one gets confused by what happens at
> read time versus compile time.  Wrapping readtable setup in (eval-when
> (:compile-toplevel) ...) may or may not help compile-file properly read
> forms which depend on this setup.
> 
> The spec says "Successive forms are read from the file by compile-file
> and processed..."  My intereptation of this is that each top level form
> is read completely and then processed before the next top level form is
> read.

That's mine, too.

> However:
> 
>  1. Others might not agree.

There was a lot of discussion about this and I think it was the intent.
Sandra Loosemore and Dave Moon went over this fairly heavily.  They would
be the right people to ask, but I doubt either reads this newsgroup.

>  2. Others might agree, yet still choose to write their compiler
> differently.  I.e., they might read the whole file first before doing
> anything that might allow eval-when :compile-toplevel.

I don't think this is valid.  Tons of my code would break if you did
this.  I've never seen it break in that way.

> Just because *I*
> think that's non-conforming doesn't mean that everyone will feel that
> they are compelled to comply.  I think there are some very good reasons
> for choosing to implement compile-file that way, and I can't fault
> anyone for doing so.

I would. ;-)  I think there are some important programs you can't write
if implementors do that, and I think there is a strong desire to write
them.  Some macros like DEFSTRUCT would have a hard time doing their own
definition since the accessors and class definitions have to be immediately 
available for use by the next form in the file.  What else would you use
to implement this but EVAL-WHEN if you broke EVAL-WHEN this way?

>  3. If you wrap the readtable setup in the proper eval-when and have the
> whole thing appear at top level, the best you can hope to do is have
> remaining TOP-LEVEL forms read correctly.

Certainly this should work, but I think you can expect better.

>  4. There are other issues that aren't about read time vs. compile time,
> but that's another story.  (1. If you side effect the readtable and the
> readtable is the same one used by your top-level, then you are side
> effecting it and subsequent compilations as well.  2. On the other hand,
> there is no way to permanently set the *readtable* variable from within
> a source file.)

Btw, for related fun with aggressive read-time evaluation, see my 
just-for-fun article originally published in Lisp Pointers):
"Ambitious Evaluation"
 http://world.std.com/~pitman/PS/Ambitious.html
If you don't know how the Lisp Machine "rubout handler"/"input editor"
technology worked, or if you have never seen "Ambitious Evaluation"
(the opposite of Lazy Evaluation, of course :-), this is a must read.
From: Vassil Nikolov
Subject: Re: load-time-value
Date: 
Message-ID: <7fqhtd$ejv$1@nnrp1.dejanews.com>
In article <···············@world.std.com>,
  Kent M Pitman <······@world.std.com> wrote:
> "Howard R. Stearns" <······@elwood.com> writes:
(...)
> >  2. Others might agree, yet still choose to write their compiler
> > differently.  I.e., they might read the whole file first before doing
> > anything that might allow eval-when :compile-toplevel.
>
> I don't think this is valid.  Tons of my code would break if you did
> this.  I've never seen it break in that way.
(...)

Let me just add that CLtL was pretty explicit that reading the
whole file first (as if it is wrapped up in a (potentially huge)
PROGN, as I imagine it) was a practice of the past, which would
not be continued with Common Lisp.  I am sorry I don't have the
book at hand right now, but it's at one of the places that
discusses top-level forms, either the Miscellaneous Features
chapter (about the compiler) or the Packages chapter (about the
compile-time effects of EXPORT & Co., now reorganised), I think.

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: R. Matthew Emerson
Subject: Re: load-time-value
Date: 
Message-ID: <87btgf2jwu.fsf@nightfly.apk.net>
Vassil Nikolov <········@poboxes.com> writes:
> 
> Let me just add that CLtL was pretty explicit that reading the
> whole file first (as if it is wrapped up in a (potentially huge)
> PROGN, as I imagine it) was a practice of the past, which would
> not be continued with Common Lisp.

CLtL2, p. 262.

-matt
From: Kelly Murray
Subject: Re: load-time-value
Date: 
Message-ID: <3720F768.64E98506@IntelliMarket.Com>
My parallel CL system compiled files in parallel by having
three processes, a reader process which read the file,
a compiler process that compiled the forms, and an assembler/output
process that generated the output.  This compiled files about 3 times
faster than a single processor implementation.  
Depending on serial processing each form would break this processing.
I introduced a #.(eval-when-read ...)
form that evaled the form and then returned it, for easier 
compatibility with "legacy" code.

I also note that even with a single processor system, it is faster
to read the entire file, then compile, then output, because it
significantly increases cache hits by not switching 
working sets all the time.

In my opinion, batch file-based "Makefile/Defsystem" application
structure is/should be replaced by persistent form-based 
"memory resident" structure that views the application as an
evolving whole, as Xerox did it 20 years ago using non-database
technology.

-Kelly Murray   ···@niclos.com


Vassil Nikolov wrote:
> 
> In article <···············@world.std.com>,
>   Kent M Pitman <······@world.std.com> wrote:
> > "Howard R. Stearns" <······@elwood.com> writes:
> (...)
> > >  2. Others might agree, yet still choose to write their compiler
> > > differently.  I.e., they might read the whole file first before doing
> > > anything that might allow eval-when :compile-toplevel.
> >
> > I don't think this is valid.  Tons of my code would break if you did
> > this.  I've never seen it break in that way.
> (...)
> 
> Let me just add that CLtL was pretty explicit that reading the
> whole file first (as if it is wrapped up in a (potentially huge)
> PROGN, as I imagine it) was a practice of the past, which would
> not be continued with Common Lisp.  I am sorry I don't have the
> book at hand right now, but it's at one of the places that
> discusses top-level forms, either the Miscellaneous Features
> chapter (about the compiler) or the Packages chapter (about the
> compile-time effects of EXPORT & Co., now reorganised), I think.
> 
> --
> Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
> (You may want to cc your posting to me if I _have_ to see it.)
>    LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)
> 
> -----------== Posted via Deja News, The Discussion Network ==----------
> http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own
From: Tim Bradshaw
Subject: Re: load-time-value
Date: 
Message-ID: <ey3ogkeuz94.fsf@lostwithiel.tfeb.org>
* Kelly Murray wrote:

> In my opinion, batch file-based "Makefile/Defsystem" application
> structure is/should be replaced by persistent form-based 
> "memory resident" structure that views the application as an
> evolving whole, as Xerox did it 20 years ago using non-database
> technology.

I kind of like this idea, but, having used the Xerox system, it's
important to remember that it was a real nightmare sometimes.  I
forget the details but I remember spending hours and hours trying to
understand really obscure problems with it, and it was extraordinarily
unrobust against the machine crashing.  It's very easy to have these
glowing memories of things, and really forget the problems.

I think your point (I removed the text) about reading-then-compiling
being better performance-wise is really good.  Fortunately, I think,
Lisps typically escape the C++ nightmare where compile time limits
productivity because you don't have to recompile the whole huge system
for every tiny change.  Where I work just now (a C/C++ place) we spend
a *lot* of time worrying about build performance.  So maybe this
doesn't matter in practice.

--tim
From: Vassil Nikolov
Subject: Re: load-time-value
Date: 
Message-ID: <7fujb1$nap$1@nnrp1.dejanews.com>
In article <·················@IntelliMarket.Com>,
  Kelly Murray <···@IntelliMarket.Com> wrote:
> My parallel CL system compiled files in parallel by having
              ^^
> three processes, a reader process which read the file,
> a compiler process that compiled the forms, and an assembler/output
> process that generated the output.  This compiled files about 3 times
> faster than a single processor implementation.
> Depending on serial processing each form would break this processing.
> I introduced a #.(eval-when-read ...)
> form that evaled the form and then returned it, for easier
> compatibility with "legacy" code.

A strange kind of _Common_ Lisp system you have there.

I see no compatibility with what you call `legacy code.'  `Eval
when reading' is *not* the same as `eval when compiling' (i.e.
read-time is not compile-time).

> I also note that even with a single processor system, it is faster
> to read the entire file, then compile, then output, because it
> significantly increases cache hits by not switching
> working sets all the time.

Before talking about speed, what about functionality?  How do you
make sure all symbols get in the right packages?  How do you
handle reader macros introduced in the file being compiled,
i.e. things like

  ;; using #$FOO (read as (DOLLARS FOO)) in this file:
  (eval-when (:compile-toplevel :execute)  ;add :load-toplevel if needed
    (set-dispatch-macro-character #\# #\$ #'|#$-reader|))  ;CLtL 22.1.5

  (defparameter *target-exchange-rate* #$1.05 "Financial stuff.")

> In my opinion, batch file-based "Makefile/Defsystem" application
> structure is/should be replaced by persistent form-based
> "memory resident" structure that views the application as an
> evolving whole, as Xerox did it 20 years ago using non-database
> technology.

`Batch' and `persistent memory-resident' both have a place under
the sun.  None of them should be considered as a universal
replacement for the other.

> Vassil Nikolov wrote:
(...)
> > Let me just add that CLtL was pretty explicit that reading the
> > whole file first (as if it is wrapped up in a (potentially huge)
> > PROGN, as I imagine it) was a practice of the past, which would
> > not be continued with Common Lisp.  I am sorry I don't have the
> > book at hand right now
(...)

Thanks to Ralph Matthew Emerson for posting the page number.  I'll
post the whole excerpt as I think it is useful.

  Implementation Note: In the past, some Lisp compilers have read the
  entire file into Lisp before processing any of the forms.  Other
  compilers have arranged for the loader to do all of its intern
  operations before evaluating any of the top-level forms.  Neither
  of these techniques will work in a straightforward way in Common
  Lisp because of the presence of multiple packages.

Guy L. Steele, CLtL, 11.7 (text from the 1st edition carried on to
the 2nd unchanged).

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: Vassil Nikolov
Subject: Re: load-time-value
Date: 
Message-ID: <7fdubs$2cq$1@nnrp1.dejanews.com>
In article <···············@world.std.com>,
  Kent M Pitman <······@world.std.com> wrote:
(...)
> I was really talking less about "times" and more about "environments".
> The compile time and runtime environments are conceptually different;
> the runtime and loadtime environment are different only in the sense
> that a cons is different before and after you rplacd it; change of state,
> not change of identity.
(...)

This, and environments in general, also deserve treatment in a textbook.

By the way, since Lisp is rich in environment-related things but still
it does not have everything thinkable (e.g. EVAL does not take an
environment argument (it is not the point here if this is good or bad)),
a textbook might also teach---besides how to use Lisp---how Lisp could
be improved (and why some obvious improvements are not such great ideas
after all).

(I remember the proverb that even one hundred lashes on somebody else's
back are too few; even one hundred suggestions are too few when
somebody else is going (or supposed) to write the textbook...  In
other words, next time I make a suggestion, I'd better have the
draft of a chapter ready...)

> I believe the failure to teach "times" (in the eval-when sense) is one
> of the most obvious gaps in computer science textbooks.

But the silver lining of this in my case at least was the satisfaction
I got when I started to figure out some of this myself.

> Some
> languages give you access to more than others do, but they are always
> relevant in all languages--in some languages only becuase you can tell
> that the reason that programs don't work is that the language failed
> to give you access to the right "time".  Lisp isn't perfect
> either--absence of access to finalization time in Lisp was recently
> noted on this newsgroup as another.

No language is perfect, of course, but Lisp is very good as a basis
to distinguish and explain program writing time, read time, compile
time, load time, run time, finalisation time, high time, quick time,
full time, part time, show time...

> There are a few other obvious things like this which I hope to include
> in my book.

Good luck!

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: David Bakhash
Subject: Re: load-time-value
Date: 
Message-ID: <wk4sme31vu.fsf@mit.edu>
thanks, Kent.  It's a good example, though I'm not 100% on it.  Maybe
after a nite's sleep it'll make some more sense in the morning.

thanks,
dave
From: Vassil Nikolov
Subject: Re: load-time-value
Date: 
Message-ID: <7fbt2b$fhe$1@nnrp1.dejanews.com>
In article <··················@acs5.bu.edu>,
  David Bakhash <·····@bu.edu> wrote:
> I read the examples in the HS, but I can't seem to figure out when this would
> be useful.  Would someone explain how this can be useful?  a really useful
> thing would be to show how to accomplish what load-time-value does given the
> rest of Lisp (e.g. eval-when, etc.)

I don't think it is possible to make a _usable_ approximation of
LOAD-TIME-VALUE using the rest of Lisp, even with EVAL-WHEN with
:LOAD-TOPLEVEL and :EXECUTE.

LOAD-TIME-VALUE replaced the now extinct sharp-comma (#,) reader
macro; the Common Lisp designers did it right the second time.

As Kent Pitman wrote, one would really understand its usefulness
on facing an actual (not contrived) problem where it is needed.

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: David Bakhash
Subject: Re: load-time-value
Date: 
Message-ID: <cxj676uoux6.fsf@acs5.bu.edu>
Vassil Nikolov <········@poboxes.com> writes:

> As Kent Pitman wrote, one would really understand its usefulness
> on facing an actual (not contrived) problem where it is needed.

I can't agree on this one.  I wasn't actually expecting anyone to deliver a
useful example (anytime soon), but surely one exists.  I don't think
load-time-value is a lesson learned in life like dealing with a romantic
relationship.  I remember when I learned what progv was, and up till then, I
hadn't seen it, and hadn't felt I needed something like it.  but after I was
shown what it did, I felt better, and when the time came that I needed it, I
was happy to have known about it beforehand.  Of course, if I were put on the
spot right now, this instant, I might have trouble fabricating an example of
its utility, but that's only because I'm not a great instructor -- not because
it's so nebulous that an instructive example does not exist.

when I looked up load-time-value in DejaNews someone mentioned that it was
(not exactly, but something like) an (eval-when (something) ...) inside an
(eval-when (something-else)).  But I didn't understand that one either, and
thought that maybe it was not a well thought-out remark, and I didn't want to
waste too much time trying to understand it.

The hyperspec requires a lot of interpretation to me.  In a lot of ways, it's
not explicit, and does not try in any way to teach computer science.  That's
what I love like it.  And like someone mentioned earlier, even a formal CS
education can't necessarily make understanding the design of a language so
simple.

thanks,
dave
From: Kent M Pitman
Subject: Re: load-time-value
Date: 
Message-ID: <sfwemliyntj.fsf@world.std.com>
David Bakhash <·····@bu.edu> writes:

> Vassil Nikolov <········@poboxes.com> writes:
> 
> > As Kent Pitman wrote, one would really understand its usefulness
> > on facing an actual (not contrived) problem where it is needed.
> 
> I can't agree on this one.  I wasn't actually expecting anyone to deliver a
> useful example (anytime soon), but surely one exists.  I don't think
> load-time-value is a lesson learned in life like dealing with a romantic
> relationship.

Well, think of it like a space of "places in time-space" that you would
like to evaluate something.  Other operators haphazardly cover the space
in ways that sometimes overlap.  For example, EVAL-WHEN papers some of
the compile-time, load-time, and run-time space.  MACROs cover compile-time
space with weird overlap onto run-time as illustrated by the problem someone
was just having with EVAL during a macro body.  DEFVAR is a mechanism for
shifting evaluation from run-time to load-time, so that by named reference
you can refer to something done at load-time.  LOAD-TIME-VALUE is
the anonymous form of same, and really only gets used when circumstances
conspire to make it useful.  Compare this to anonymous inline functions,
that is, lambda combinations.  How often do you see

 ((lambda (x) (+ x 3)) 4)

in production code, and yet once in a while it does come up--and certainly
it is foundational to what goes on in the language.
We used to make people confront lambda combinations first-thing when I
learned Lisp, and I just about never ended up learning Lisp because it
was so ugly and confusing as it was taught at that time.  Nowadays, many
people learn Lisp without ever confronting lambda combinations, and I have
to say I don't think that's all bad.  The Scheme people are very "in your face"
about functions and functional programming, but I am more of the school that
people should "know the tool is there" and use it if it feels good.
Most computation can be expressed in more than one way while still being
intelligible.  People should exploit that flexibility to allow themselves
to be comfortable, not see that flexibility as an impediment to be solved.

In my experience, the people who need load-time-value *know* they need it
and ask for it spontaneously by name.  And the people who don't need it
mostly really don't.  You're worried about the middle case where someone needs
it but doesn't know it, and that's theoretically possible.  I wasn't really
trying to say you shouldn't care.  I was just saying you shouldn't panic,
and people shouldn't panic in general, for not having an immediate need
for this tool.  

Part of the problem with things like this which are added for completeness
is that some overzealous teachers insist people learn the complete set right
away.  Viz recent discussion of people wanting to learn the type tree before
using Lisp.  That teaching style, taken to the nth,  becomes a burden for
language designers who find themselves feeling they must not add more features
to the language because they feel for people who end up in classes taught
by people who say they must learn the whole set before they use the language.

I know full well I don't need to know all of Java to use it, but boy does it
bug me how many textbooks on Java are organized as complete walks across
all of the available options rather than as guided walks through what is
really needed to write simple things, and what is a good way to discover more
gradually.

>  I remember when I learned what progv was, and up till then, I
> hadn't seen it, and hadn't felt I needed something like it.  but
> after I was shown what it did, I felt better, and when the time came
> that I needed it, I was happy to have known about it beforehand.  Of
> course, if I were put on the spot right now, this instant, I might
> have trouble fabricating an example of its utility, but that's only
> because I'm not a great instructor -- not because it's so nebulous
> that an instructive example does not exist.

PROGV is another excellent example, actually.  I know of only two good
uses for PROGV -- one is for allowing a set of bindings that are 
user-customizable around a command loop, as in:
 (defvar *command-loop-bindings* '((*print-length* 3) (*read-base* 8)))
 (defun command-loop () 
   (progv (mapcar #'first *command-loop-bindings*)
	  (mapcar #'second *command-loop-bindings*)
      (really-command-loop)))
Although I prefer the LispM progw, which permits a binding list style
so you can just (progw *command-loop-bindings* (really-command-loop)).
The other is for implementing embedded interpreters, as in:
 (cond ((eq (car form) 'let)
        (progv (mapcar #'first (cadr form))
	       (mapcar #'(lambda (x) (my-eval (second x))) (cadr form))
           (my-eval `(progn ,@(cddr form))))) ...)
I'll try to put this in my book and then you can point your students
to that. ;-)
 
> when I looked up load-time-value in DejaNews someone mentioned that it was
> (not exactly, but something like) an (eval-when (something) ...) inside an
> (eval-when (something-else)).  But I didn't understand that one either, and
> thought that maybe it was not a well thought-out remark, and I didn't want to
> waste too much time trying to understand it.

load-time-value is to a special variable reference
as 
a lambda expression is to a named function refrence.
 
more or less.

does that analogy help? or just make it more obscure?
all the anonymous things get less play.  not none, but less.
there are not any anonymous macros, though some people have observed
the occasional need. for macros i always write
 (macrolet ((do-it () ...)) (do-it))
when i want an anonymous macro.  and that mostly suffices.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <m2aew62x9w.fsf@wizard.kraut.bc.ca>
Kent M Pitman <······@world.std.com> writes:
>
> Joachim Achtzehnter <·······@kraut.bc.ca> writes:
> >
> > Is it acceptable to call eval on macro arguments in that case?
> 
> Macros that are "only called at runtime" are not really macros.
> It really is bad form to do this.

You're right, if anything you never know whether somebody might not
try to use the macro in a source file some day.

> Can you offer a simple example so we can try to propose a clean
> alternative?

Rather than coming up with an example (the code is at the office), let
me try to explain what I'm trying to do. What I have is actually
working fine, so this discussion is not about getting it working, but
about doing it in a better way.

Some background: We have a system that must provide different views
for different customers. It is an object-oriented design with a large
number of inter-related classes. The customized views are created by
defining virtual entities, a virtual instance of which is represented
by a group of actual objects in the model. These virtual entities have
virtual attributes (derived from attributes on actual model objects)
which can be viewed in a user interface.

What I was trying to do was to use syntax similar to defclass to
define such a virtual entity and its attributes, and to automatically
generate the code which constructs the virtual data from the actual
model objects. The main reason for using a macro instead of a function
was the desire to pass an unquoted symbol as the virtual entity's
name. This was, of course, easily achieved by using a macro, but then
all arguments remained un-evaluated. For some arguments it was often
convenient to pass symbolic constants which I _wanted_ evaluated,
hence my mis-guided use of eval.

One solution is to simply force callers to quote symbols, then I can
use functions. I guess, what you're saying is that if I want to use
macros I'll have to move the parts that need evaluation into the macro
expansion itself, so that it always happens at runtime. I'll play a
little more with this on Monday.

Joachim
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfw1zhiyr2z.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> What I was trying to do was to use syntax similar to defclass to
> define such a virtual entity and its attributes, and to automatically
> generate the code which constructs the virtual data from the actual
> model objects. The main reason for using a macro instead of a function
> was the desire to pass an unquoted symbol as the virtual entity's
> name. This was, of course, easily achieved by using a macro, but then
> all arguments remained un-evaluated. For some arguments it was often
> convenient to pass symbolic constants which I _wanted_ evaluated,
> hence my mis-guided use of eval.
> 
> One solution is to simply force callers to quote symbols, then I can
> use functions. I guess, what you're saying is that if I want to use
> macros I'll have to move the parts that need evaluation into the macro
> expansion itself, so that it always happens at runtime. I'll play a
> little more with this on Monday.

This is precisely one of the reasons FEXPRs existed in Maclisp:
to accomodate people's desire to type (TRACE FOO) instead of (TRACE 'FOO).
That simple problem led to all manner of hassle when people wanted to
TRACE variable quantities later, having to allow them to do
(APPLY 'TRACE (LIST x)) where X was a variable quantity.  FEXPRs,
unlike MACROs, could be applied.  My 1980 paper goes into all of this
and I think you'll find it helpful.
 http://world.std.com/~pitman/Papers/Special-Forms.html

The real issue isn't the adding of quotation, it's the places where 
non-quotation would happen.  It's not (TRACE FOO) => (*TRACE 'FOO)
that is problematic for a macro, since EVAL is not called.  It's
(FROB FOO (+ X 2)) => (*FROB 'FOO 7) that is a problem because the
X has to evaluate in some context.  Better to write either
(FROB FOO (+ X 2)) => (*FROB 'FOO (+ X 2)) or
(FROB FOO (+ X 2)) => (*FROB 'FOO '(+ X 2)) ;to be EVAL'd at runtime
or
(FROB FOO (+ X 2)) => (*FROB 'FOO #'(LAMBDA () (+ X 2))) ;to be FUNCALL'd at runtime
or
(FROB FOO (+ X 2)) => (*FROB 'FOO (LOAD-TIME-VALUE (+ X 2))) ;evaluated by the system at loadtime and effectively a constant at runtime

If access to the lexical environment is important, the closure form is
necessary and you can't escape calling the function on every access because
the lexical environment changes on each call, and you can only give access
to it by repeatedly accessing it.  Both the LOAD-TIME-VALUE and to-be-EVAL'd
forms effectively only have access to the dynamic environment.  The
version where you just output (+ X 2) instead of #'(LAMBDA () (+ X 2))
differs only in that the latter delays evaluation so that you can 
instantiate additional dynamic environment before running it, or so that you
can elect not to call it it at all (permits conditional evaluation).

Pardon this being so terse.  I'm trying to type this out quickly before
breakfast.  I hope you can make some sense of it.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <uciuas5wan.fsf@soft.mercury.bc.ca>
Kent M Pitman <······@world.std.com> writes:
> 
> Can you offer a simple example so we can try to propose a clean
> alternative?

Ok, let me give you a slightly simplified example of one of the macros
I wrote. This omits some aspects which are not relevant to the issue
at hand, I hope this doesn't obscure the purpose of the macro too
much.

The macro define-entity-type defines a virtual type which doesn't have
any presistent instances, instead, the type's functionality is
implemented in terms of other types. The virtual instances exist only
as object ids which contain sufficient information to find the
relevant real objects.

The macro accepts an unquoted symbol as its name, followed by an
integer which is used as a type marker inside the object id, followed
by a function (lambda expression or function name). It creates an
object which stores this meta information, and also generates and
stores functions that implement the virtual type's functionality.
Typically these generated functions include calls to the passed-in
function.

The macro would be called like this:

(defconstant +some-integer-constant+ 42)
(define-entity-type my-entity
   +some-integer-constant+
   #'(lambda (oid) (locate-true-instance oid)))

Currently the macro is defined like this (as mentioned earlier the
actual macro is somewhat more complicated):

(defmacro define-entity-type (entity-name oid-type instance-finder)
  (let ((self (make-instance 'entity-type)))
    (setf (entity-name self) entity-name)
    (setf (oid-type self) (eval oid-type))  ; want integer
    (setf (finder self) (eval instance-finder)) ; want function object
    (generate-functions self) ; generates functions that funcall finder
    self))

Presumably, some of the body should somehow be moved into a
backquote expression so that it evaluates at loadtime?

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfw4smcbcc3.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> Kent M Pitman <······@world.std.com> writes:
> > Can you offer a simple example so we can try to propose a clean
> > alternative?
> Ok, let me give you a slightly simplified example [...]
> The macro would be called like this:
> 
> (defconstant +some-integer-constant+ 42)
> (define-entity-type my-entity
>    +some-integer-constant+
>    #'(lambda (oid) (locate-true-instance oid)))
> 
> Currently the macro is defined like this (as mentioned earlier the
> actual macro is somewhat more complicated):
> 
> (defmacro define-entity-type (entity-name oid-type instance-finder)
>   (let ((self (make-instance 'entity-type)))
>     (setf (entity-name self) entity-name)
>     (setf (oid-type self) (eval oid-type))  ; want integer
>     (setf (finder self) (eval instance-finder)) ; want function object
>     (generate-functions self) ; generates functions that funcall finder
>     self))
> 
> Presumably, some of the body should somehow be moved into a
> backquote expression so that it evaluates at loadtime?

That's what I'd do, yes.

(defmacro define-entity-type (entity-name oid-type instance-finder)
  `(declare-entity-type ',entity-name ,oid-type ,instance-finder))

(defun declare-entity-type (entity-name oid-type instance-finder)
  (check-type oid-type integer)
  (check-type instance-finder function)
  (let ((self (make-instance 'entity-type)))
    (setf (entity-name self) entity-name)
    (setf (oid-type self) oid-type)
    (setf (finder self) instance-finder)
    (generate-functions self)
    self))

Note that in addition to the other problems you had, your macro was
expanding into '#<entity...> which means you were having to dump out
a literal entity object which creates a burden to set up make-load-form
if you tried to really compile this.  A reimplementation such as I've
done here doesn't require a make-load-form because the declare-entity-type
is executed at execute-time (either load time or runtime, depending
on whether this is a top-level form).

For obvious reasons, I didn't test this.

Useful macro tip:

 Rather than call EVAL, see if you can make your macro expand so that
 the thing you want to EVAL is in the natural path of the evaluation
 the system is going to do anyway.  You get one EVAL for free--the one
 the system provides.  It's best to use that one because it and it alone
 has access to the lexical context.  Consider:

 (let ((x +some-integer-constant+))
  (define-entity-type foo x #'(lambda (oid) (locate-true-instance oid))))

 My definition has half a chance of getting this right, but yours will
 lose because the EVAL will find X unbound.  It won't see the lexical
 binding of X wrapped around the define-entity-type form.

 Ditto in the finder:

 (flet ((locate-true-instance (x) (locate-true-instance x)))
  (define-entity-type foo +whatever+ #'(lambda (oid) (lti oid))))

 Again here, you want the lexical environment when evaluating the finder
 form.  This will also help if you do just
 (locally (declare (optimize (speed 3) (safety 0)))
  (define-entity-type foo +whatever+ #'(lambda (oid) (lti oid)))  )


Incidentally,
 #'(lambda (oid) (locate-true-instance oid))
is better written
 #'locate-true-instance
unless locate-true-instance takes more than one arg and you're afraid
whoever you're giving it to will call it with args you don't want them
to call it with.  Wrapping an extra lambda around it doesn't really do
anything other than allow you to document the name of the arg and slow
the call down in case the compiler doesn't notice to optimize the wrapper
back out.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <uciuasytxk.fsf@soft.mercury.bc.ca>
Kent M Pitman <······@world.std.com> writes:
> 
> That's what I'd do, yes.
> 
> (defmacro define-entity-type (entity-name oid-type instance-finder)
>   `(declare-entity-type ',entity-name ,oid-type ,instance-finder))
> 
> (defun declare-entity-type (entity-name oid-type instance-finder)
> ...

Ok, the coin has dropped. :-) In order to get an effect similar to
defclass which can be called with an unquoted symbol, one writes an
ordinary function which must be called with a quoted symbol. Then
write a macro which expands into a call to that function with the
relevant argument(s) quoted. Thanks.

> For obvious reasons, I didn't test this.

It works, I have tried it with my more complicated macro which has to
deal with a keyword argument consisting of a list whose elements are
lists containing unquoted symbols. Quoting these nested symbols was a
little more tricky, but still straightforward after you showed the
way.

> Useful macro tip:
> 
>  Rather than call EVAL, see if you can make your macro expand so that
>  the thing you want to EVAL is in the natural path of the evaluation
>  the system is going to do anyway.  You get one EVAL for free--the one
>  the system provides.  It's best to use that one because it and it alone
>  has access to the lexical context.

Since we trying to avoid explicit use of eval, I wonder whether I
should be able to avoid another use of eval in my generate-functions
method. This method constructs a lambda expression based on meta data
in enetity-type and stores the function object in a slot. It does
something like this:

(defmethod generate-functions ((self entity-type))
  (setf (get-instances self)
     ;; can (should?) this eval be avoided too?
     (eval `#'(lambda (oid)
                ;; some stuff constructed from entity-type slots
                ))))

> Incidentally,
>  #'(lambda (oid) (locate-true-instance oid))
> is better written
>  #'locate-true-instance

Yes, in the actual code the lambda expression did more than simply
call another function.

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfw1zhguhx4.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> (defmethod generate-functions ((self entity-type))
>   (setf (get-instances self)
>      ;; can (should?) this eval be avoided too?
>      (eval `#'(lambda (oid)
>                 ;; some stuff constructed from entity-type slots
>                 ))))
> 

It's hard to tell from what you said.  If it's really put together out
of s-expression, then it might not be avoidable.  Probably I'd use
 (compile nil '(lambda ....))
if indeed you need to do this, since it means you won't be running 
interpreted in systems that use an interpreter.

However, if I saw more of the stuff you were using to construct stuff,
I wonder if I'd see you could get away with closures instead of functional
construction. e.g., instead of 
 (eval `#'(lambda (oid) ,(if foo 'something 'something-else)))
use
 #'(lambda (oid) (if foo something something-else))
or
 (if foo #'(lambda (oid) something) #'(lambda (oid) something-else))
The main place you'd use eval or compile instead would be if these
were going to be too slow.  But note that the mere mentioning of 
either compile or eval makes your application image necessarily
much larger, since many applications ought to be constructable without
either eval or compile.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <ucogkjozr3.fsf@soft.mercury.bc.ca>
Kent M Pitman <······@world.std.com> writes:
>
> It's hard to tell from what you said... if I saw more of the stuff
> you were using... 

Ok, trying to avoid posting a lot of code was obviously
counterproductive :-)

Here are some examples of the stuff I'm using, this time only error
handling is omitted.

(defmethod generate-functions ((self entity-type))
  (setf (get-keys self)
    (compile
     nil
     (eval `#'(lambda (oid)
                (values
                  ,@(mapcar
                      #'(lambda (lookup)
                           `(funcall ,(key-finder lookup) oid))
                      (key-lookups self)))))))
  (setf (get-instances self)
    (let ((arg-list (mapcar
                     #'(lambda (ignored)
                          (declare (ignore ignored))
                          (gensym))
                     (key-lookups self))))
      (compile
       nil
       (eval `#'(lambda (oid)
                  (multiple-value-bind ,arg-list
                        (funcall ,(get-keys self) oid)
                    (values
                     ,@(mapcar
                        #'(lambda (traversal)
                            `(funcall ,(instance-finder traversal)
                                ,@arg-list))
                        (entity-traversals self))))))))))
Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwzp42hd7x.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> > It's hard to tell from what you said... if I saw more of the stuff
> > you were using... 
> 
> Ok, trying to avoid posting a lot of code was obviously
> counterproductive :-)

Well, I've been enjoying reading your text posts, so I don't know if
it was wasted. 

> Here are some examples of the stuff I'm using, this time only error
> handling is omitted.
> 
> (defmethod generate-functions ((self entity-type))
>   (setf (get-keys self)
>     (compile
>      nil
>      (eval `#'(lambda (oid)
>                 (values
>                   ,@(mapcar
>                       #'(lambda (lookup)
>                            `(funcall ,(key-finder lookup) oid))
>                       (key-lookups self)))))))
>   (setf (get-instances self)
>     (let ((arg-list (mapcar
>                      #'(lambda (ignored)
>                           (declare (ignore ignored))
>                           (gensym))
>                      (key-lookups self))))
>       (compile
>        nil
>        (eval `#'(lambda (oid)
>                   (multiple-value-bind ,arg-list
>                         (funcall ,(get-keys self) oid)
>                     (values
>                      ,@(mapcar
>                         #'(lambda (traversal)
>                             `(funcall ,(instance-finder traversal)
>                                 ,@arg-list))
>                         (entity-traversals self))))))))))

I spent only literally about 5-10 minutes doing this rewrite, so don't
expect it to be perfect, but hopefully it's enough to give you the idea
of what I was getting at.  I definitely did not test this.

(defmethod generate-functions ((self entity-type))
  (setf (get-keys self)
        (let* ((key-lookups (key-lookups self))
               (key-finders (mapcar #'key-finder key-lookups)))
          #'(lambda (oid)
              (values-list (mapcar #'(lambda (kf) (funcall kf oid))
                                   key-finders)))))
  (setf (get-instances self)
        (let ((finder-args (get-keys self))
	      (finder (instance-finder traversal))
              (traversals (entity-traversals self)))
          #'(lambda (oid)
              (values-list
                (mapcar #'(lambda (traversal)
                            (apply  traversal finder-args))
                        finder-args))))))

A couple of things to note:

 * Most obviously, htere is no eval or compile in this version.

 * The idiom (values-list (mapcar ...)) is going to cons where your
   application originally did not, so there is some loss of efficiency.
   You have to trade that against the loss of efficiency for having your
   application possibly be several megabytes bigger if you include the
   compiler and/or evaluator where it is not needed.  Also, the compiler
   *could* optimize this idiom.  There is a workaround which some
   compilers might do better on if you observed them doing very bad
   code here... You could write something which consed a stack list
   one-by-one (taking up a comparatively huge amount of stack space
   for each list cell because you'd have to have a whole function call
   stack  frame at each cons cell, but at least it would not require
   the compiler to be as smart.  The compiler would still have to do
   stack-allocation of rest vectors but that's more common than some
   other things.  You *might* also get better code from some compilers
   with:
    (let ((x (mapcar ...)))
      (declare (dynamic-extent x))
      (values-list x))
   but I bet probably not. (sigh)   The alternative I was alluding to
   that is more likely to work, though, is:
    (defun map-values (fn items)
      (labels ((map-values-internal (items &rest kludge)
                 (if (null items)
                     (values-list kludge)

                     (apply #'map-values-internal
                            (cdr items)
                            (funcall fn (car items)) ;stack-cons 1 result
                            kludge))))
        (map-values-internal items)))
   I never tried doing this before, but it seemed like it should work.
   Indeed, I checked it in both LW 4.1 Personal and Allegro 5.0 and both
   cons up the whole list for (values-list (mapcar ...)) before discarding
   it in favor of multiple-return values; it would be nice if they
   (and all implementations) would optimize this idiom.  But both 
   implementations do not cons when you do this map-values kludge I wrote.
   I guess you can score one for us having added enough fun linguistics 
   to the language that there was something I could say to "explain" to
   the language what I wanted, but at the same time I have to admit that
   this is a serious kludge the average beginning programmer would probably
   not think of.  [Note that I normally don't recommend recursive solutions
   to traversing lists--in favor of iterative things, but in this particular
   case I am *using* the stack as my data structure and I'm making use of
   CL's willingness to not optimize this tail call.  (This might not do
   the right thing if you have tail call optimizations on; I didn't test
   that. Adding (declare (optimize (debug 3))) along with the dynamic extent
   declaration  might be a good thing to hope it wouldn't get tail-call
   optimized, but there isn't a reliable/portable incantation for that.)
   And this is also making use of the fact that if you were willing
   to do (values ...) to get back the values, you probably didn't have
   a very long list of values, so I figured it wasn't that expensive to
   make a mess on the stack trying to accumulate the values to return.

Hope this gives you some useful ideas.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <m2u2uas7ll.fsf@wizard.kraut.bc.ca>
Thanks again for your expert advise. Before getting to your comments I
would like to ask a few questions about specific parts of my original
code. 

> Joachim Achtzehnter <·······@kraut.bc.ca> writes:
> 
> > (defmethod generate-functions ((self entity-type))
> >   (setf (get-keys self)
> >     (compile
> >      nil
> >      (eval `#'(lambda (oid)
> >                 (values
> >                   ,@(mapcar

Was it necessary to use both compile and eval here? Could this have
been avoided without changing the basic design? I don't mind the
compile (see below for more on this), but I seem to remember not being
able to get by without the eval. Is this because of the use of
backquotes?

> >     (let ((arg-list (mapcar
> >                      #'(lambda (ignored)
> >                           (declare (ignore ignored))
> >                           (gensym))
> >                      (key-lookups self))))

Is there a better idiom for generating a list of symbols of equal
length as an existing list? One that doesn't require the 'ignored'
hack?

Kent M Pitman <······@world.std.com> writes:

> I spent only literally about 5-10 minutes doing this rewrite, so don't
> expect it to be perfect, but hopefully it's enough to give you the idea
> of what I was getting at.  I definitely did not test this.
> 
> (defmethod generate-functions ((self entity-type))
>   (setf (get-keys self)
>         (let* ((key-lookups (key-lookups self))
>                (key-finders (mapcar #'key-finder key-lookups)))
>           #'(lambda (oid)
>               (values-list (mapcar #'(lambda (kf) (funcall kf oid))
>                                    key-finders)))))
>   (setf (get-instances self)
>         (let ((finder-args (get-keys self))
> 	      (finder (instance-finder traversal))
>               (traversals (entity-traversals self)))
>           #'(lambda (oid)
>               (values-list
>                 (mapcar #'(lambda (traversal)
>                             (apply  traversal finder-args))
>                         finder-args))))))

Using compile would presumably increase runtime performance of these
functions?

> A couple of things to note:
> 
>  * Most obviously, htere is no eval or compile in this version.
> 
>  * The idiom (values-list (mapcar ...)) is going to cons where your
>    application originally did not, so there is some loss of efficiency.
>    You have to trade that against the loss of efficiency for having your
>    application possibly be several megabytes bigger if you include the
>    compiler and/or evaluator where it is not needed.

This is part of a large application which literally uses several
hundreds of megabytes of memory due to data which is kept in memory. A
few megabytes more won't even be noticed. And eval is already being
used in a few other places, not all of my making, I'm only one of the
wheels in this project :-)

Keeping this in mind would you still go for one of your suggested
alternatives? Your 'clean' version above is more compact and easier to
understand than my explicit construction of values forms. But the use
of mapcar at runtime is somewhat less efficient (unless this is
optimized away). As you correctly guessed, the lists are not very
long, but several instances of these functions will be generated by
the application, the functions will be called moderately often, and
there is a small chance that in a future release of the system the
generated functions may end up being called in a loop.

>    You could write something which consed a stack list
>    one-by-one (taking up a comparatively huge amount of stack space
>    for each list cell because you'd have to have a whole function call
>    stack  frame at each cons cell, but at least it would not require
>    the compiler to be as smart.  The compiler would still have to do
>    stack-allocation of rest vectors but that's more common than some
>    other things.
>
>     (defun map-values (fn items)
>       (labels ((map-values-internal (items &rest kludge)
>                  (if (null items)
>                      (values-list kludge)
> 
>                      (apply #'map-values-internal
>                             (cdr items)
>                             (funcall fn (car items)) ;stack-cons 1 result
>                             kludge))))
>         (map-values-internal items)))

Are you saying that this is faster in spite of the recursion?  This
certainly wouldn't have occured to me. Allocating cons cells via the
cons form must then be a lot worse in terms of performance than
allocating stack frames?

Joachim
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwhfqai1y3.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> > > (defmethod generate-functions ((self entity-type))
> > >   (setf (get-keys self)
> > >     (compile
> > >      nil
> > >      (eval `#'(lambda (oid)
> > >                 (values
> > >                   ,@(mapcar
> 
> Was it necessary to use both compile and eval here? Could this have
> been avoided without changing the basic design? I don't mind the
> compile (see below for more on this), but I seem to remember not being
> able to get by without the eval. Is this because of the use of
> backquotes?

(compile nil '(lambda ...)) is entirely sufficient if you need to compile
something.  It is specified that it will be coerced to a function by COMPILE,
so you might think there's no harm in calling COMPILE, but you cannot detect
that it is coerced to a function before compilation, and so you can't be
sure it's the same heavy-weight mechanism as EVAL, so you should prefer to
let COMPILE do it by the most lightweight thing it can get away with.

 > >     (let ((arg-list (mapcar
> > >                      #'(lambda (ignored)
> > >                           (declare (ignore ignored))
> > >                           (gensym))
> > >                      (key-lookups self))))
> 
> Is there a better idiom for generating a list of symbols of equal
> length as an existing list? One that doesn't require the 'ignored'
> hack?

I hate this idiom myself.  I don't know a good answer.  I actually think
it'd be nice if there were a gensym-variant just for this purpose.  On
the Lisp Machine, the answer was that the variable IGNORE was magic and
could be duplicated and would never be complained about, so 
 (mapcar #'(lambda (ignore) (gensym)) ...)
was enough.  But I'd like a (mapcar #'gensym1 ...) with a better name,
perhaps, that one could use without the #'lambda.  Probably best under
the circumstances is (loop for x in ... collect (gensym)) since at least
it's compact, if not functional.
 
> Kent M Pitman <······@world.std.com> writes:
> 
> > I spent only literally about 5-10 minutes doing this rewrite, so don't
> > expect it to be perfect, but hopefully it's enough to give you the idea
> > of what I was getting at.  I definitely did not test this.
> > 
> > (defmethod generate-functions ((self entity-type))
> >   (setf (get-keys self)
> >         (let* ((key-lookups (key-lookups self))
> >                (key-finders (mapcar #'key-finder key-lookups)))
> >           #'(lambda (oid)
> >               (values-list (mapcar #'(lambda (kf) (funcall kf oid))
> >                                    key-finders)))))
> >   (setf (get-instances self)
> >         (let ((finder-args (get-keys self))
> > 	      (finder (instance-finder traversal))
> >               (traversals (entity-traversals self)))
> >           #'(lambda (oid)
> >               (values-list
> >                 (mapcar #'(lambda (traversal)
> >                             (apply  traversal finder-args))
> >                         finder-args))))))
> 
> Using compile would presumably increase runtime performance of these
> functions?

These functions will already be compiled as long as you compile the file
containing this definition of generate-functions.  The physical manifestation
of #'(lambda ...) at runtime is to create an object of type closure [not a
CL type--just a conceptual type most implementations use] which is 
effectively no different than a cons of a primitive function and some hidden
arguments representing the closed-over data.  There is nothing very
inefficient about that.  You'll maybe get a couple instructions better with
your approach becasue in essence you're doing
 (values (foo) (bar) (baz))
where I'm doing
 (values-list (mapcar ...))
[which does a tiny bit of extra consing--the gc overhead for which is the
main obstacle, not the execution itself] or
 (map-values ..)
[which pushes more stack than yours].  But this code above does not run
interpreted if that is your fear.

> > A couple of things to note:
> > 
> >  * Most obviously, htere is no eval or compile in this version.
> > 
> >  * The idiom (values-list (mapcar ...)) is going to cons where your
> >    application originally did not, so there is some loss of efficiency.
> >    You have to trade that against the loss of efficiency for having your
> >    application possibly be several megabytes bigger if you include the
> >    compiler and/or evaluator where it is not needed.
> 
> This is part of a large application which literally uses several
> hundreds of megabytes of memory due to data which is kept in memory. A
> few megabytes more won't even be noticed. And eval is already being
> used in a few other places, not all of my making, I'm only one of the
> wheels in this project :-)
> 
> Keeping this in mind would you still go for one of your suggested
> alternatives?

Yes.  But performance metering will tell you the answer.  There is no
subsitute for trying both and comparing their performance.  If you can
avoid your strategy--that is, if you feel its an issue of stylistic
discretion, my sense is that I would let that discretion always fall
away from EVAL.  EVAL is a bigger hammer, and I prefer personally to 
have its use imply an inability not to use it which I don't see here.
But sometimes performance wins over discretion, and that's life.

> Your 'clean' version above is more compact and easier to
> understand than my explicit construction of values forms.

Ease of maintenance is one of the reasons.

> But the use
> of mapcar at runtime is somewhat less efficient (unless this is
> optimized away). As you correctly guessed, the lists are not very
> long, but several instances of these functions will be generated by
> the application, the functions will be called moderately often, 

That they will be called a lot is the issue that worries me in deciding
if you have to go with your approach.  Your approach quite naturally
approaches a tighter optimum becuase it conceptually places Lisp farther
up the chain of design back to the point of being party as "original
programmer" (albeit programmatically).  The original programmer always
can tune things better.  But that's a very much more complicated meta-area
of code to be in and ill be harder to maintain a lot of the time, more
opaque to others looking at your code, etc.  It is not to be avoided 
entirely--just to be used sparingly as an out--sort of like the way
Superman doesn't use his ability to travel around the world really fast
and go back in time to change history to solve every problem he has.  He
COULD do this to get cats out of trees by making sure they never got stuck
there in the first place, but it's more dramatic if he only uses it to 
rescue Lois after her occasional death. ;-)

> and
> there is a small chance that in a future release of the system the
> generated functions may end up being called in a loop.

If they're not called a LOT of the time such that the cycles involved
are a substantial contributor to the overall slowness of your system,
I would take the approach that avoids EVAL and COMPILE.

The attempt to hyper-optimize parts of your system that are not in the
inner loop are (IMO) one of the most common and senseless ways to 
make a system obscure to read and hard to maintain.

> >    You could write something which consed a stack list
> >    one-by-one (taking up a comparatively huge amount of stack space
> >    for each list cell because you'd have to have a whole function call
> >    stack  frame at each cons cell, but at least it would not require
> >    the compiler to be as smart.  The compiler would still have to do
> >    stack-allocation of rest vectors but that's more common than some
> >    other things.
> >
> >     (defun map-values (fn items)
> >       (labels ((map-values-internal (items &rest kludge)
> >                  (if (null items)
> >                      (values-list kludge)
> > 
> >                      (apply #'map-values-internal
> >                             (cdr items)
> >                             (funcall fn (car items)) ;stack-cons 1 result
> >                             kludge))))
> >         (map-values-internal items)))
> 
> Are you saying that this is faster in spite of the recursion?  This
> certainly wouldn't have occured to me. Allocating cons cells via the
> cons form must then be a lot worse in terms of performance than
> allocating stack frames?

I doubt it's faster, but as I mentioned, it's the GC time that kills you.

GC is a problem not unlike the sewer system in your city.  They tell
you not to waste water, but a lot of the time it doesn't matter.
Incremental use of water has no cost, but there is a big step function
if you run out of water or if your sewer's capacity is exceeded--then
there is NO water.  Same with GC.  Cosing a little is not so bad
sometimes, but consing at all is always a risk that you're going to
get hit with this relatively large cost of doing a collection.  If
this gets called a lot, garbage will pile up and sometimes you'll get
an avoidable delay.  Overall, I think having a GC'd system is good and
this price is worth paying--but it's not worth being frivolous about
consing if you can avoid it.  I freely cons in functions that don't
get called much but in anything I think is called as part of a core
system that is running constantly, I like to work by induction making
each one function avoid consing as much as it can and hope the goodwill
adds up.  Often, though, this is a resource issue and it's not something
you can spend time on.  That's one reason I wrote this MAP-VALUES as a
modular function--so you can use it in other places where this comes up
and not just here, getting some leverage for the time spent on the 
distraction of microoptimizing.
From: Gareth McCaughan
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <86pv4y9fka.fsf@g.pet.cam.ac.uk>
Kent M Pitman <······@world.std.com> writes:

> > > >     (let ((arg-list (mapcar
> > > >                      #'(lambda (ignored)
> > > >                           (declare (ignore ignored))
> > > >                           (gensym))
> > > >                      (key-lookups self))))
> > 
> > Is there a better idiom for generating a list of symbols of equal
> > length as an existing list? One that doesn't require the 'ignored'
> > hack?
> 
> I hate this idiom myself.  I don't know a good answer.  I actually think
> it'd be nice if there were a gensym-variant just for this purpose.  On
> the Lisp Machine, the answer was that the variable IGNORE was magic and
> could be duplicated and would never be complained about, so 
>  (mapcar #'(lambda (ignore) (gensym)) ...)
> was enough.  But I'd like a (mapcar #'gensym1 ...) with a better name,
> perhaps, that one could use without the #'lambda.  Probably best under
> the circumstances is (loop for x in ... collect (gensym)) since at least
> it's compact, if not functional.

    (mapcar #'copy-symbol (key-lookups self))

?

-- 
Gareth McCaughan       Dept. of Pure Mathematics & Mathematical Statistics,
·····@dpmms.cam.ac.uk  Cambridge University, England.
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwhfqam0b3.fsf@world.std.com>
Gareth McCaughan <·····@dpmms.cam.ac.uk> writes:

>     (mapcar #'copy-symbol (key-lookups self))

I thought of this, but discarded it, perhaps prematurely.
You're assuming key-lookups returns a symbol.  I wasn't.  In general,
you can need a list of gensyms corresponding to any list of objects.
But you're right that if this function *does* return a symbol, this
would be happy.  (And if the function returns a string, make-symbol works
instead of copy-symbol... :-)
From: Gareth McCaughan
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <86n201appe.fsf@g.pet.cam.ac.uk>
Kent Pitman wrote:

[I suggested:]
>>     (mapcar #'copy-symbol (key-lookups self))
> 
> I thought of this, but discarded it, perhaps prematurely.
> You're assuming key-lookups returns a symbol.  I wasn't.  In general,
> you can need a list of gensyms corresponding to any list of objects.

*thud*[1] Quite right.

I suppose that if you have an application where this kind of thing
comes up often, it might be worth doing

    (declaim (inline ignoring-arg))
    (defun ignoring-arg (f) #'(lambda (x) (declare (ignore x)) (funcall f x)))

at the outset, and then

    (mapcar (ignoring-arg #'gensym) (key-lookups self))

It's still nasty.

> But you're right that if this function *does* return a symbol, this
> would be happy.  (And if the function returns a string, make-symbol works
> instead of copy-symbol... :-)

Bleurgh. :-)


[1] Sound of head hitting wall.

-- 
Gareth McCaughan       Dept. of Pure Mathematics & Mathematical Statistics,
·····@dpmms.cam.ac.uk  Cambridge University, England.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <ucyajlygwr.fsf@soft.mercury.bc.ca>
Gareth McCaughan <·····@dpmms.cam.ac.uk> writes:
>
> (defun ignoring-arg (f) #'(lambda (x) (declare (ignore x)) (funcall f x)))

Or better, to make the declaration consistent with reality:

(defun ignoring-arg (f) #'(lambda (x) (declare (ignore x)) (funcall f)))

:-)

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Gareth McCaughan
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <8690bkzyxr.fsf@g.pet.cam.ac.uk>
Joachim Achtzehnter wrote:

[I stupidly suggested:]
>> (defun ignoring-arg (f) #'(lambda (x) (declare (ignore x)) (funcall f x)))
> 
> Or better, to make the declaration consistent with reality:
> 
> (defun ignoring-arg (f) #'(lambda (x) (declare (ignore x)) (funcall f)))

Oops. :-)

-- 
Gareth McCaughan       Dept. of Pure Mathematics & Mathematical Statistics,
·····@dpmms.cam.ac.uk  Cambridge University, England.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <uc3e1tzx4q.fsf@soft.mercury.bc.ca>
Kent M Pitman <······@world.std.com> writes:
>
> Gareth McCaughan <·····@dpmms.cam.ac.uk> writes:
> 
> >     (mapcar #'copy-symbol (key-lookups self))
> 
> I thought of this, but discarded it, perhaps prematurely.
> You're assuming key-lookups returns a symbol.  I wasn't.

They are not symbols in this case, they are function objects, unnamed
function objects in most cases.

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Barry Margolin
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <l1oT2.84$fQ1.7751@burlma1-snr2>
I have no idea who wrote:
>> > Is there a better idiom for generating a list of symbols of equal
>> > length as an existing list? One that doesn't require the 'ignored'
>> > hack?

How about:

(loop repeat (length (key-lookups self))
      collect (gensym))

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Erik Naggum
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <3133702798486404@naggum.no>
* Joachim Achtzehnter <·······@kraut.bc.ca>
| Is there a better idiom for generating a list of symbols of equal length
| as an existing list? One that doesn't require the 'ignored' hack?

* Kent M Pitman <······@world.std.com>
| I hate this idiom myself.  I don't know a good answer.  I actually think
| it'd be nice if there were a gensym-variant just for this purpose.  On
| the Lisp Machine, the answer was that the variable IGNORE was magic and
| could be duplicated and would never be complained about, so
|  (mapcar #'(lambda (ignore) (gensym)) ...)
| was enough.  But I'd like a (mapcar #'gensym1 ...) with a better name,
| perhaps, that one could use without the #'lambda.  Probably best under
| the circumstances is (loop for x in ... collect (gensym)) since at least
| it's compact, if not functional.

  in the standard, we find under MAP-INTO an alluring example that doesn't
  work (A is a list of four elements prior to this snippet):

(map-into a #'gensym) =>  (#:G9090 #:G9091 #:G9092 #:G9093)

  somebody clearly thought this was a sufficiently good idea that it
  _should_ have worked...

#:Erik
From: Barry Margolin
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sboT2.85$fQ1.7751@burlma1-snr2>
In article <················@naggum.no>, Erik Naggum  <····@naggum.no> wrote:
>  in the standard, we find under MAP-INTO an alluring example that doesn't
>  work (A is a list of four elements prior to this snippet):
>
>(map-into a #'gensym) =>  (#:G9090 #:G9091 #:G9092 #:G9093)
>
>  somebody clearly thought this was a sufficiently good idea that it
>  _should_ have worked...

Why doesn't that work?  I don't have a Common Lisp implementation handy to
try it on, but I just entered the sample definition in the Notes into Emacs
Lisp, and the above example worked.  Does the sample definition not match
the description in some critical way?

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <ucu2u9yfkn.fsf@soft.mercury.bc.ca>
Barry Margolin <······@bbnplanet.com> writes:
>
> Erik Naggum  <····@naggum.no> wrote:
> >  in the standard, we find under MAP-INTO an alluring example
> >  that doesn't work
> >
> >(map-into a #'gensym) =>  (#:G9090 #:G9091 #:G9092 #:G9093)
> 
> Why doesn't that work?

According to the Hypespec it ought to work. The Hyperspec says
map-into could be defined by:

 (defun map-into (result-sequence function &rest sequences)
   (loop for index below (apply #'min 
                                (length result-sequence)
                                (mapcar #'length sequences))
         do (setf (elt result-sequence index)
                  (apply function
                         (mapcar #'(lambda (seq) (elt seq index))
                                 sequences))))
   result-sequence)

With this definition the example works. But somehow the built-in
map-into in Allegro 5 returns the original list unchanged. Seems
Allegro's map-into misbehaves when the function is not followed by at
least one argument sequence. Is this a bug in Allegro? Does it work in
other implementations?

However, even when it works, this doesn't quite do what I was
originally looking for because map-into destructiuvely modifies the
result-sequence. Seems, the suggested solutions using loop are the
answer.

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Barry Margolin
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <v6pT2.92$fQ1.7751@burlma1-snr2>
In article <··············@soft.mercury.bc.ca>,
Joachim Achtzehnter  <·······@kraut.bc.ca> wrote:
>However, even when it works, this doesn't quite do what I was
>originally looking for because map-into destructiuvely modifies the
>result-sequence. Seems, the suggested solutions using loop are the
>answer.

(map-into (copy-list <expression>) #'gensym)

should solve the destructivity problem.

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Arthur Lemmens
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <371E3096.436F41D9@simplex.nl>
Erik Naggum  <····@naggum.no>:
>  in the standard, we find under MAP-INTO an alluring example
>  that doesn't work
>
>(map-into a #'gensym) =>  (#:G9090 #:G9091 #:G9092 #:G9093)

Barry Margolin <······@bbnplanet.com>:
> Why doesn't that work?

Joachim Achtzehnter:
> somehow the built-in map-into in Allegro 5 returns the original list 
> unchanged. Seems Allegro's map-into misbehaves when the function is 
> not followed by at least one argument sequence. Is this a bug in 
> Allegro? Does it work in other implementations?

Works fine in LWW 4.14:

CL-USER 57 > (setq a (list 1 2 3 4))
(1 2 3 4)

CL-USER 58 > (map-into a #'gensym)
(#:G15610 #:G15611 #:G15612 #:G15613)

CL-USER 59 > a
(#:G15610 #:G15611 #:G15612 #:G15613)

Arthur Lemmens
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfwaew1ab9h.fsf@world.std.com>
Arthur Lemmens <·······@simplex.nl> writes:

> Erik Naggum  <····@naggum.no>:
> >(map-into a #'gensym) =>  (#:G9090 #:G9091 #:G9092 #:G9093)
> 
> Barry Margolin <······@bbnplanet.com>:
> > Why doesn't that work?
> 
> Works fine in LWW 4.14:

Just make sure  the list is always fresh if you're going to side-effect it.
From: Vassil Nikolov
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7fh16b$p3n$1@nnrp1.dejanews.com>
In article <···············@world.std.com>,
  Kent M Pitman <······@world.std.com> wrote:
(...)
> (defmacro define-entity-type (entity-name oid-type instance-finder)
>   `(declare-entity-type ',entity-name ,oid-type ,instance-finder))
>
> (defun declare-entity-type (entity-name oid-type instance-finder)
>   (check-type oid-type integer)
>   (check-type instance-finder function)
>   (let ((self (make-instance 'entity-type)))
>     (setf (entity-name self) entity-name)
>     (setf (oid-type self) oid-type)
>     (setf (finder self) instance-finder)
>     (generate-functions self)
>     self))

Let me add things that will hopefully be useful.

In general, a defining device can be implemented as a function
or a macro.  Reasons why it should be a macro include (but are
probably not limited to):

* need to have definition-related things happen at compile-time
  (by expanding into an explicit EVAl-WHEN or into another
  special form or macro that has similar functionality), e.g.
  DEFPACKAGE;

* need to have a declarative syntax of the defining form, all of
  whose subforms would be known at compile time,---not just to
  avoid cluttering it with quotes, but to let the compiler know
  that what it is compiling is (literal) source code, not some
  (quoted literal) data.

Absence of backquotes is just a symptom that such reasons might
not be actually present (sometimes; such absence does not
always mean that the programmer wants a function, really;
after all, every macro can be written without backquote, only
more painfully).

One example of such declarative syntax is a DEFGENERIC form
which may have components like (:DOCUMENTATION ...) or
(:METHOD ...).  An example about the relationship between
a macro as a defining device and a function as a defining
device is DEFCLASS expanding into a call to ENSURE-CLASS.^1
__________
^1 Note that this example is a Common Lisp example but not
   an ANSI Common Lisp example since the ANSI standard did
   not include this part of CLOS; many implementation do it
   this way, so don't look into the HyperSpec, look into
   your implementation's documentation and/or call MACROEXPAND
   of a DEFCLASS form, or look into the _Art of MOP_ (see the
   FAQ for a reference).)

Now, one of the points I am driving at is that I do not
consider the desire to save a quote in front of a symbol
to be good reason for implementing a defining device as
a macro rather than as a function.  (Of course, there
may be other considerations related to the project of
the original poster, but they are not involved in this
discussion.)

In other words, in my book a macro is not `a function
that does not evaluate its arguments.'

The simplest illustration I can think of is not with
a defining form, but it is the same idea.

Consider (SETQ FOO VALUE) vs. (SET 'FOO VALUE).  Although
SETQ started that way (as the name also suggests (correct
me if I'm wrong)), the two forms are not equivalent at all.
SETQ operates on a variable, i.e. on a program entity; SET
operates on a symbol, i.e. on a piece of data.  (Well, yes,
symbols are used to represent variables etc. etc., but I
hope the meaning is clear, and if I had to formulate the
above rigorously, I would have needed a couple of paragraphs,
not a couple of lines, and wouldn't have done it all.
Although Lisp programs are represented as Lisp data, this
does not mean such distinctions cannot be made.)

(It's good that SET is still with us, although deprecated,
otherwise I would have had to explain what it does.)

I would say there is a common desire among Lisp programmers,
or at least many of them, to want to save typing the quotes,
and they find macros as the tool that would allow them to do
it.  For the reasons I tried to explain above (not the perfect
explanation I suppose), programmers should overcome this desire.

> Note that in addition to the other problems you had, your macro was
> expanding into '#<entity...> which means you were having to dump out

A linguistic note about `Lisp English':

Can't help noting that the above sentence should be interpreted
with care.  It means that the expansion was _the value of_
(QUOTE #<entity...>), not that _the form into which the macro
expanded_ was (QUOTE #<entity...>):  consider that the last form
in the body of the original macro definition (sorry for not including
it here, but it was essentially the body of the DEFUN of
DECLARE-ENTITY-TYPE above) was SELF and not `',SELF (i.e.
not `(QUOTE ,SELF)), and the value of (the local variable) SELF
was an instance.

This is the same way of expressing oneself as in: "blah-blah returns
'FOO" which is the same as, but more concise than, "blah-blah returns
the symbol FOO"^2 and is used to avoid misunderstanding "blah-blah
returns FOO" (sans the quote) as if the value of the variable FOO were
returned.  Or compare:

  (LIST '+ '2 '4) returns '(+ 2 4).
  (LIST '+ '2 '4) returns the list (+ 2 4).
  (* 2 3) returns (+ 2 4).
  (* 2 3) returns [the integer] 6.

__________
^2 and which does not mean "blah-blah returns a list of two elements,
   the symbol QUOTE and the symbol FOO"

<;-)> Permission is granted for the unrestricted use of the above
two paragraphs or any portions thereof, in the same form or adapted
as necessary, in Lisp textbooks or other educational material. </;-)>

> a literal entity object which creates a burden to set up make-load-form
> if you tried to really compile this.  A reimplementation such as I've
> done here doesn't require a make-load-form because the declare-entity-type
> is executed at execute-time (either load time or runtime, depending
> on whether this is a top-level form).

To me, if a macro expansion returns a data object and not a form,
this is a sign that the programmer might not really want a macro
for the functionality that is to be achieved.  The reason for this
is more general than a desire to avoid a need for MAKE-LOAD-FORM
(since the data object might be just a number or a symbol) and,
to repeat others and myself, is related to the fact that the objects
which macro expansion functions operate on and return are program
forms, not program data, from the point of view of the macro user.

Yet another way to illustrate my meaning: with

  (defun foo (x) (+ x 1))

FOO is a `compile-time symbol' while with

  (setf (symbol-function 'foo) (lambda (x) (+ x 1)))

FOO is a `run-time symbol.'  Now, you are supposed to ask the
question: with (FOO 0), is FOO a compile-time symbol or a run-time
symbol?  The answer is that it depends on the rest of the program.
If the programmer won't ever do SETF of SYMBOL-FUNCTION of FOO,
then they may also say, in addition to the DEFUN,

  (declaim (inline foo))

and inform the compiler that whenever FOO appears as the first
element of a form that is to be evaluated, it is a compile-time
FOO and there is no need for the compiler to arrange that the
function to be called is found by lookup of FOO's function cell.
On the other hand, if the possibility of SETF of SYMBOL-FUNCTION
of FOO (or EVAL of DEFUN of FOO) at run time exists, then FOO
in a `function call position' must be treated as a run-time FOO
(and its function cell examined), and the programmer would say

  (declaim (notinline foo))

to instruct (not inform!) the compiler about this.

For a complete treatment of [NOT]INLINE, see the literature
(in particular, how this can also be done locally, and how
INLINE may be ignored by the compiler, unlike NOTINLINE).

__________
By the way, execute-time (as used by Kent Pitman) is also
another important term in the xxx-time set.  (Though the
meaning of `execute' in this phrase is not quite the same
as in the EVAL-WHEN situation :EXECUTE.)

Another point: though I did not have that in mind when I
started, now I see that using the above terminology, it
is easy to formulate one of the reasons why keywords are
special: they always are both compile-time and run-time
symbols.  (The other reason is that they work in the same
way no matter what the current package is.)

(...)
> Useful macro tip:
>
>  Rather than call EVAL, see if you can make your macro expand so that
>  the thing you want to EVAL is in the natural path of the evaluation
>  the system is going to do anyway.  You get one EVAL for free--the one
>  the system provides.  It's best to use that one because it and it alone
>  has access to the lexical context.

Such advice, and more of the same kind on writing macros, deserves to
appear in good textbooks.  Unlike stuff about packages, environments,
etc., however, which is apparently not covered by existing textbooks,
issues like the above should already be discussed in the literature.
(Though I can't recall what exactly Norvig's book explains about macros,
and I haven't seen Graham's books.)

Since there ain't no such thing as a free eval, may I suggest the
phrase `you have the inalienable right to one eval, by placing your
form in a for-evaluation position'...  (And of course, Lisp instructors
should read out to students their rights.)

(...)  ;the rest of the quoted article omitted

Unrelated to the above, but may help some to understand macros better.
If we compare Lisp to another language such as C with respect to macros,
C macros are analogous to Lisp reader macros, not to Lisp DEFMACRO
macros.

I hope you may find this post at least half as useful as it is long.

--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: Joachim Achtzehnter
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <ucso9vp1ic.fsf@soft.mercury.bc.ca>
Vassil Nikolov <········@poboxes.com> writes:
> 
> Let me add things that will hopefully be useful.
>
> [a lot of useful advise omitted]

Thanks.

It will take me a while before I can really absorb all your advise. In
the meantime I would like to comment on one point:

> Now, one of the points I am driving at is that I do not
> consider the desire to save a quote in front of a symbol
> to be good reason for implementing a defining device as
> a macro rather than as a function.

In my case, the motivation behind the desire to avoid the quote had
little to do with issues along the lines of `saving a keystroke'. My
motivation was based on the observation that the 'virtual entity' I
was defining with this form, in many ways, is semantically similar to
a CLOS class. Being able to define two similar entites (CLOS classes
and my virtual entities) using similar forms seemed useful to me, if
only because it is easier to remember the syntax (and whether or not
to quote symbols in certain places :-). In addition to that argument,
the fact that the language designers themselves had decided to provide
the defclass macro in this way suggested to me that a similar macro
for a comparable purpose may well be sensible.

Would you consider these to be good reasons?

Joachim

-- 
·······@kraut.bc.ca      (http://www.kraut.bc.ca)
·······@mercury.bc.ca    (http://www.mercury.bc.ca)
From: Kent M Pitman
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <sfw1zheitnr.fsf@world.std.com>
Joachim Achtzehnter <·······@kraut.bc.ca> writes:

> > Now, one of the points I am driving at is that I do not
> > consider the desire to save a quote in front of a symbol
> > to be good reason for implementing a defining device as
> > a macro rather than as a function.
> 
> the fact that the language designers themselves had decided to provide
> the defclass macro in this way suggested to me that a similar macro
> for a comparable purpose may well be sensible.

I agree.  While quotation per se may be iffy to some people, I think
there's a fine line between quotation qua "end goal" and quotation qua
implementation technique for creating a new "namespace".  DEFCLASS
is a good example where a quasi-namespace of class names is created
in a way that would seem more "pedestrian" if you had to use a quoted
symbol.  One reason Lisp is good for implementing "embedded languages"
and for "making users feel like they can extend the language" (vs just
"add functions") is this ability to parrot what the system does, not
just in power but in form.

> Would you consider these to be good reasons?

Yes.
From: ··········@scientia.com
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7fmmgr$u3b$1@nnrp1.dejanews.com>
In article <··············@soft.mercury.bc.ca>,
  Joachim Achtzehnter <·······@kraut.bc.ca> wrote:

>                                         In addition to that argument,
> the fact that the language designers themselves had decided to provide
> the defclass macro in this way suggested to me that a similar macro
> for a comparable purpose may well be sensible.


This thing that I have come across on at least one occasion is that similar
macros are exported from a package and the only of defining certain objects.
If you want to make such an entity on the fly at runtime you would therefore
have to do something with eval and macroexpand.

In the case of defclass you're OK because it's a thin wrapper, and you can use
other things to make a class.

Actually I'm slightly hazy on precisely what you can do within the langauge
spec (as opposed to what works with the compiler I use): e.g. the CLOS MOP
gives you ensure-class, but this isn't in the CL Hyperspec.


-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own    
From: Vassil Nikolov
Subject: Re: return-from / defmacro question
Date: 
Message-ID: <7fqhsg$ejn$1@nnrp1.dejanews.com>
In article <··············@soft.mercury.bc.ca>,
  Joachim Achtzehnter <·······@kraut.bc.ca> wrote:
> Vassil Nikolov <········@poboxes.com> writes:
(...)
> > Now, one of the points I am driving at is that I do not
> > consider the desire to save a quote in front of a symbol
> > to be good reason for implementing a defining device as
> > a macro rather than as a function.
>
> In my case, the motivation behind the desire to avoid the quote had
> little to do with issues along the lines of `saving a keystroke'. My
> motivation was based on the observation that the 'virtual entity' I
> was defining with this form, in many ways, is semantically similar to
> a CLOS class. Being able to define two similar entites (CLOS classes
> and my virtual entities) using similar forms seemed useful to me, if
> only because it is easier to remember the syntax (and whether or not
> to quote symbols in certain places :-). In addition to that argument,
> the fact that the language designers themselves had decided to provide
> the defclass macro in this way suggested to me that a similar macro
> for a comparable purpose may well be sensible.
>
> Would you consider these to be good reasons?

I could answer better if I knew more about the virtual entities in
your project, specifically about the time they are constructed.  As
it is, I'll try to give my opinion in a conditional.

If DEFINE-VIRTUAL-ENTITY is like DEFCLASS, then it is appropriate
not to evaluate the name of the entity.  If it is like (the non-ANSI
function) ENSURE-CLASS, then it is not appropriate, and the user
shouldn't be saved the quote.

Note how DEFUN, DEFMACRO, DEFCLASS, ... do not take quotes, while
MAKE-PACKAGE does evaluate its argument(s).^1  Also note that _defining_
macros, at least in the typical case, evaluate none of their arguments.
Your DEFINE-VIRTUAL-ENTITY evaluated some of them (as far as I remember)
and that made me suspicious.  Of course, I wouldn't say there can
never be some sort of a hybrid case which would be justified to do
that.
__________
^1 also consider a hypothetically useful (untested):

   > (defun make-function (name lambda-expression)
       "Create a named function at run time."
       (setf (symbol-function name)
             (coerce lambda-expression 'function))
             ;; COERCE implicitly involves EVAL or COMPILE;
             ;; some price is to be paid for constructing functions
             ;; at run time
        name)
   MAKE-FUNCTION
   > (make-function 'foo #'(lambda (x) (+ x 1)))
   FOO
   > (foo 0)
   1
   > (make-function (intern (read-line)) (read))
   user input>> BAR
   user input>> (lambda (x) (- x 1))
   BAR
   > (bar 1)
   0
   > (defmacro trivial-defun (name lambda-list &body body)
       "A bare-bones DEFUN."
       ;; this is also analogous to how DEFCLASS is implemented in AMOP
       `(make-function ,name #'(lambda ,lambda-list ,@body)))
   TRIVIAL-DEFUN


--
Vassil Nikolov <········@poboxes.com> www.poboxes.com/vnikolov
(You may want to cc your posting to me if I _have_ to see it.)
   LEGEMANVALEMFVTVTVM  (Ancient Roman programmers' adage.)

-----------== Posted via Deja News, The Discussion Network ==----------
http://www.dejanews.com/       Search, Read, Discuss, or Start Your Own