From: Don Geddis
Subject: Special forms vs. Macros
Date: 
Message-ID: <87fz1fed1p.fsf@sidious.geddis.org>
What is the difference between special forms and macros in Common Lisp?

Assume that I have a list of a few special forms and a few macros.
Presumably there is some (portable) CL function you can write to tell
the difference, and tell me how many items in my list are special forms
and how many are macros.

Is one concept a subset of the other?  Is there some property that every
special form must have, but macros are not required to have?  Or vis versa?
IIRC, ANSI allows (but doesn't require) special forms to be implemented as
macros.  Yet I suppose there may still be a crucial difference.

Note that I'm hoping for something more than a trivial "special-form-p" in
the language.  I guess the real question is, why did the ANSI committee invent
this concept of "special forms"?  How is the ANSI CL standard stronger because
that concept exists (as distinct from macros)?

        -- Don
_______________________________________________________________________________
Don Geddis                  http://don.geddis.org/               ···@geddis.org

From: Barry Margolin
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <barmar-678EFB.21093505012005@comcast.dca.giganews.com>
In article <··············@sidious.geddis.org>,
 Don Geddis <···@geddis.org> wrote:

> What is the difference between special forms and macros in Common Lisp?

Special operators have to be handled specially by the implementation.  
They implement various primitive operations that can't (easily) be 
defined in terms of other operations.

Macros simply rewrite one expression into another.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: Don Geddis
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <87fz1ecu3l.fsf@sidious.geddis.org>
Barry Margolin <······@alum.mit.edu> wrote on Wed, 05 Jan 2005:
> Special operators have to be handled specially by the implementation.  
> They implement various primitive operations that can't (easily) be 
> defined in terms of other operations.
>
> Macros simply rewrite one expression into another.

OK, but I'm still a bit confused about the utility of the concept.

The first thing that is "special" about the operators is evaluation, so
we certainly need something other than regular functions.  But macros give
us this already.

I understand that macros are simply a source-to-source translation.  But nobody
says that all macros must only rewrite into common lisp.  Presumably, there
would be a number of internal functions, and a macro version of IF or DEFUN
would rewrite into those internal function calls.  To me, this doesn't seem
much different from many CL functions, such as +, which presumably wind up
calling some internal non-CL function in order to access the hardware's
arithmetic.  Yet the CL spec doesn't separate out these ordinary CL functions
which also "can't easily be defined in terms of other operations".

In fact, the tone of the ANSI CL specification seems to be only defining
behavior, with very little commentary on implementation.  (E.g. no garbage
collection, tail call optimization, etc.)  Even if special operators do need
to be handled specially by the implementation, why does the CL spec need to
call them out as a separate class?  Presumably, any real implementation handles
all sorts of things specially.

I'm still missing the conceptual key that made everyone think, "yes, we ought
to create this different concept of special operator."  It seems to me that
if the spec had just said that IF and DEFUN were macros (leaving it up to
the implementation to decide what they expanded into), everything would have
worked just fine.  And the spec would have been simpler.

Am I wrong about this?  If the spec were written in the way I suggest, would
something else have gone wrong later that I don't see right now?

        -- Don
_______________________________________________________________________________
Don Geddis                  http://don.geddis.org/               ···@geddis.org
From: Duane Rettig
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <4is6a43y7.fsf@franz.com>
Don Geddis <···@geddis.org> writes:

> In fact, the tone of the ANSI CL specification seems to be only defining
> behavior, with very little commentary on implementation.  (E.g. no garbage
> collection, tail call optimization, etc.)  Even if special operators do need
> to be handled specially by the implementation, why does the CL spec need to
> call them out as a separate class?  Presumably, any real implementation handles
> all sorts of things specially.
> 
> I'm still missing the conceptual key that made everyone think, "yes, we ought
> to create this different concept of special operator."  It seems to me that
> if the spec had just said that IF and DEFUN were macros (leaving it up to
> the implementation to decide what they expanded into), everything would have
> worked just fine.  And the spec would have been simpler.
> 
> Am I wrong about this?  If the spec were written in the way I suggest, would
> something else have gone wrong later that I don't see right now?

Special-forms exist for the compiler and interpreter.  There is
no other difference in requirements.  The argument about conditional
evaluation is a red herring; the same effect can be easily gotten
with a macro definition.

Note that it is special-operators that are "special", not macros.
If you call macroexpand on a macro form, it _must_ expand according
to macroexpansion rules.  Special-forms do not have to do this.
If every special form were treated as a macro, then the compiler
would not be able to look at a form as that form; e.g. an IF form
would have to expand to something else, and the compiler could never
see it.  This means that the compiler would be required to wade
through the (presumably lower-level) macroexpansion of the
higher-level operator, instead of being able to recognize the
construct for what it is and compile it efficiently.  Mutatis mutandis
for interpreter treatment.

The spec is extremely lenient on this issue; any definition specified
as a macro can be implemented as a special-form, as long as a macro
definition is also available.  And any special operator can also
have a macro definition (macro definition ==> macro-function returns
a non-nil value).

In Allegro CL, which has an interpreter, we implement DO/DO* as
special operators.  DO forms can of course be macroexpanded, but
if the compiler wants to see the DO form and draw type inferences or
rewrite it with strength reduction, it can do so, and the interpreter
can interpret a DO form directly, rather than having to macroexpand
it and thus waste more time in macroexpansion when the looping
construct is much simpler to do without the macroexpansion.

-- 
Duane Rettig    ·····@franz.com    Franz Inc.  http://www.franz.com/
555 12th St., Suite 1450               http://www.555citycenter.com/
Oakland, Ca. 94607        Phone: (510) 452-2000; Fax: (510) 452-0182   
From: Peter Seibel
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <m3r7kyz9if.fsf@javamonkey.com>
Don Geddis <···@geddis.org> writes:

> I'm still missing the conceptual key that made everyone think, "yes,
> we ought to create this different concept of special operator." It
> seems to me that if the spec had just said that IF and DEFUN were
> macros (leaving it up to the implementation to decide what they
> expanded into), everything would have worked just fine. And the spec
> would have been simpler.

Well, for starters, DEFUN *is* a macro. But that aside, if you did
what you said, then you'd have two classes of macros--those that can
be written to expand only into other macros and functions defined the
standard[1] and those (such as IF, if it was a macro) that have to
expand into something implementation defined. The macros in the second
class would probably be more or less the special operators--ones that
do stuff like introduce new lexically scoped names (LET, LET*, FLET,
LABELS, MACROLET, SYMBOL-MACROLET, BLOCK, and TAGBODY), use lexically
scoped names (SETQ, RETURN-FROM, and GO) control evaluation (IF,
QUOTE, and PROGN) communicate with the compiler (EVAL-WHEN, PROGN,
LOAD-TIME-VALUE, THE, and LOCALLY), create dynamic bindings (PROGV),
muck with the call stack (CATCH, THROW, UNWIND-PROTECT), and deal with
multiple values, (MULTIPLE-VALUE-CALL and MULTIPLE-VALUE-PROG1).

Obviously they might get sliced different ways by different
implementations but they'd all have some set of "primitive" macros
that interact with the implementation in ways that other macros do
not. Because the standard explicitly calls out a set, you have at
least a chance of writing a tree walker--you know exactly which
operators are special and have to be understood specially by your tree
walker. Anything else is either a function and you know how to walk it
or a macro which you can expand and then walk.[2]

-Peter

[1] Which is not to say that all such macros necessary *are*
implemented that way in any given Common Lisp implemetation. That is,
if you macroexpand a DEFUN you may well see calls to
implementation-specific functions. But those are usually--it seems to
me--for things that are not strictly required by the spec such as
recording source locations.

[2] Unfortunately this doesn't quite work because the standard doesn't
require the standard macros to ultimately expand only into functions
or special operators--an implementation, as I understand it, could
have its own "special operators", upon which a general-purpose tree
walker would choke. But at least user-code should be walkable.

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Barry Margolin
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <barmar-1C5D63.20230706012005@comcast.dca.giganews.com>
In article <··············@sidious.geddis.org>,
 Don Geddis <···@geddis.org> wrote:

> In fact, the tone of the ANSI CL specification seems to be only defining
> behavior, with very little commentary on implementation.  (E.g. no garbage
> collection, tail call optimization, etc.)  Even if special operators do need
> to be handled specially by the implementation, why does the CL spec need to
> call them out as a separate class?  Presumably, any real implementation 
> handles
> all sorts of things specially.

Common Lisp provides a number of "introspection" features, which are 
useful for applications that deal with code as data.  If you're writing 
a code-walker, you need to know which expressions are normal function 
calls, versus the ones that must be handled specially by the 
implementation.

If all the special forms were macros that expand into 
implementation-dependent expressions that are treated specially, these 
types of applications would not have any way of recognizing that they've 
reached a primitive.

Also, any of the special treatment that an implementation provides for 
ordinary forms is generally just an optimization.  For instance, the 
fact that (+ a b c) is compiled directly into machine code rather than a 
FUNCALL of the + function.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: M Jared Finder
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <3441j5F467qseU1@individual.net>
Don Geddis wrote:
> What is the difference between special forms and macros in Common Lisp?
> 
> Assume that I have a list of a few special forms and a few macros.
> Presumably there is some (portable) CL function you can write to tell
> the difference, and tell me how many items in my list are special forms
> and how many are macros.

(count-if #'special-operator-p list)
(count-if #'macro-function list)

> Is one concept a subset of the other?  Is there some property that every
> special form must have, but macros are not required to have?  Or vis versa?
> IIRC, ANSI allows (but doesn't require) special forms to be implemented as
> macros.  Yet I suppose there may still be a crucial difference.
 >
> Note that I'm hoping for something more than a trivial "special-form-p" in
> the language.  I guess the real question is, why did the ANSI committee invent
> this concept of "special forms"?  How is the ANSI CL standard stronger because
> that concept exists (as distinct from macros)?

The CLHS defines a special operator as follows:

special operator n. one of a fixed set of symbols, enumerated in Figure 
3-2, that may appear in the car of a form in order to identify the form 
as a special form.

The important thing here is that the set of symbols that are special 
operators are *fixed*.  This allows you to look at any Lisp form and 
know what subforms could be evaluated and which can't.  This is useful 
if you want to write EVAL as a Lisp function.

   -- MJF
From: Don Geddis
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <87k6qqcupv.fsf@sidious.geddis.org>
M Jared Finder <·······@digipen.edu> wrote on Wed, 05 Jan 2005:
> The important thing here is that the set of symbols that are special
> operators are *fixed*.  This allows you to look at any Lisp form and know
> what subforms could be evaluated and which can't.  This is useful if you want
> to write EVAL as a Lisp function.

I'm not sure how this helps me.  Surely whatever special casing you need
to do for special operators, you also need to do for macros.

Or are you saying that in order to write EVAL, you actually have to
_implement_ all the special operators within your code, but you can simply
FUNCALL the functions, and MACROEXPAND the macros?

Yet it would seem that you wouldn't need this distinction, if CL's
special operators had been specified to be macros also.

        -- Don
_______________________________________________________________________________
Don Geddis                  http://don.geddis.org/               ···@geddis.org
From: Cameron MacKinnon
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <oKydnVDcjqGvGUDcRVn-rA@golden.net>
Don Geddis wrote:
> I'm not sure how this helps me.  Surely whatever special casing you need
> to do for special operators, you also need to do for macros.
> 
> Or are you saying that in order to write EVAL, you actually have to
> _implement_ all the special operators within your code, but you can simply
> FUNCALL the functions, and MACROEXPAND the macros?

Precisely.

The difference between the special operator IF and the primitive 
operator that implements addition is that one of IF's subforms won't get 
evaluated, whereas primitive-+ has its arguments evaluated before it is 
called.
From: Adrian Kubala
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <slrnctranl.qkt.adrian@sixfingeredman.net>
Don Geddis <···@geddis.org> schrieb:
> Or are you saying that in order to write EVAL, you actually have to
> _implement_ all the special operators within your code, but you can simply
> FUNCALL the functions, and MACROEXPAND the macros?
>
> Yet it would seem that you wouldn't need this distinction, if CL's
> special operators had been specified to be macros also.

Maybe the point you're overlooking is that there is a fundamental
distinction between how "if" and, say, "not" are evaluated. "not", like
other functions, has its argument evaluated first and then passed to it.
You can't do this with "if" because if may not want all its arguments
evaluated.

Macros DO let you implement your own evaluation rules, but only by
virtue of the underlying special forms. If macros could only expand to
function applications, then they would not be able to do this. So that's
why you can implement if as a macro in terms of cond, or visa versa, but
you can't implement either without some lower-level special form. At the
very least, lambda must be a special form, musn't it?
From: Rob Warnock
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <HoOdnRFxfrS-2EPcRVn-pQ@speakeasy.net>
Adrian Kubala  <······@sixfingeredman.net> wrote:
+---------------
| Macros DO let you implement your own evaluation rules, but only by
| virtue of the underlying special forms. If macros could only expand to
| function applications, then they would not be able to do this. So that's
| why you can implement if as a macro in terms of cond, or visa versa, but
| you can't implement either without some lower-level special form. At the
| very least, lambda must be a special form, musn't it?
+---------------

LAMBDA and QUOTE, I think, and in Common Lisp, probably FUNCTION as well.
And LOAD-TIME-VALUE, for nice compilation.

Of course, you need primitve *functions* such as FUNCALL & APPLY & C[AD]*R
and arithmetic and so forth, but I think the above list are the minimum
of special forms. You also need functional forms for "setters" for all
the common data types that don't already have them, e.g. AREF! (to use
the Scheme convention), which in CMUCL is LISP::%ASET and in CLISP is
SYSTEM::STORE.

You can even do away with IF (or COND) if you have a primitive function,
say, TRUTH-NUMBER, that takes a Lisp value and returns the fixnum 0 for
true and 1 for false [or vice-versa, it doesn't matter, either can be
made to work] and arrays and accessors [as above], like so:

	(defmacro if (boolean consequent alternate)
	  `(funcall (aref (load-time-value
			    (make-array 2 :initial-contents
			                  (list (lambda () ,consequent)
					        (lambda () ,alternate)))))
		    (truth-number ,boolean)))

[Note: The LOAD-TIME-VALUE isn't cheating, only an efficiency hack.
You can do the same thing without it, though with a lot more consing...]

Hmmm... Though looking back at the discussion we has about this a
year ago, it looks like there are a *LOT* more mandatory special
forms in Common Lisp than in Scheme:

    block      let*                  return-from      
    catch      load-time-value       setq             
    eval-when  locally               symbol-macrolet  
    flet       macrolet              tagbody          
    function   multiple-value-call   the              
    go         multiple-value-prog1  throw            
    if         progn                 unwind-protect   
    labels     progv                                  
    let        quote

PROGN, LET, LET*, and FLET (maybe) can be hacked with FUNCALL & LAMBDA.
Even LABELS can be hacked with the Y operator (ugh!). SETQ can be hacked
with an appropriate set of macros and low-level setters.

But BLOCK, TAGBODY, GO, UNWIND-PROTECT, MULTIPLE-VALUE-CALL, RETURN,
RETURN-FROM, etc., I dunno. I think you're in trouble there. And you
*can't* do EVAL-WHEN in a macro, can you? And then all the declaration
stuff -- DECLAIM, DECLARE, LOCALLY, THE -- those are pretty "special"
operators.


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Adrian Kubala
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <slrncttqbj.4o1.adrian@sixfingeredman.net>
Rob Warnock <····@rpw3.org> schrieb:
> You can even do away with IF (or COND) if you have a primitive function,
> say, TRUTH-NUMBER, that takes a Lisp value and returns the fixnum 0 for
> true and 1 for false [or vice-versa, it doesn't matter, either can be
> made to work] and arrays and accessors [as above], like so:
>
> 	(defmacro if (boolean consequent alternate)
> 	  `(funcall (aref (load-time-value
> 			    (make-array 2 :initial-contents
> 			                  (list (lambda () ,consequent)
> 					        (lambda () ,alternate)))))
> 		    (truth-number ,boolean)))

It looks to me like the key part here isn't truth-number, but using
lambda to delay evaluation. I think that's how smalltalk does it in
fact: "if" is a function which takes a boolean and two thunks.
From: Rob Warnock
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <YPidnStKIIcx70LcRVn-hQ@speakeasy.net>
Adrian Kubala  <······@sixfingeredman.net> wrote:
+---------------
| Rob Warnock <····@rpw3.org> schrieb:
| > You can even do away with IF (or COND) if you have a primitive function,
| > say, TRUTH-NUMBER, that takes a Lisp value and returns [a fixnum]...
| 
| It looks to me like the key part here isn't truth-number, but using
| lambda to delay evaluation. I think that's how smalltalk does it in
| fact: "if" is a function which takes a boolean and two thunks.
+---------------

*D'oh!!* Of course, thanks! Since we were allowing more-or-less arbitrary
primitive functions in the implementation in this game in the first place,
the above could/should be simply this [with the TRUTH-NUMBER functionality
buried inside SYSTEM::%IF].

    (defmacro if (boolean consequent alternate)
      `(system::%if ,boolean (lambda () ,consequent) (lambda () ,alternate)))

Thanks!


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Peter Seibel
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <m33bxco4gh.fsf@javamonkey.com>
····@rpw3.org (Rob Warnock) writes:

> Adrian Kubala  <······@sixfingeredman.net> wrote:
> +---------------
> | Rob Warnock <····@rpw3.org> schrieb:
> | > You can even do away with IF (or COND) if you have a primitive function,
> | > say, TRUTH-NUMBER, that takes a Lisp value and returns [a fixnum]...
> | 
> | It looks to me like the key part here isn't truth-number, but using
> | lambda to delay evaluation. I think that's how smalltalk does it in
> | fact: "if" is a function which takes a boolean and two thunks.
> +---------------
>
> *D'oh!!* Of course, thanks! Since we were allowing more-or-less arbitrary
> primitive functions in the implementation in this game in the first place,
> the above could/should be simply this [with the TRUTH-NUMBER functionality
> buried inside SYSTEM::%IF].
>
>     (defmacro if (boolean consequent alternate)
>       `(system::%if ,boolean (lambda () ,consequent) (lambda () ,alternate)))

So the Smalltalkish way to do it would be:

  (defmacro if (boolean consequent alternate)
    `(funcall
       (system::as-boolean ,boolean)
       (lambda () ,consequent)
       (lambda () ,alternate)))

Where SYSTEM::AS-BOOLEAN returns either:

  (lambda (consequent alternate) (funcall consequent)) ;; true
  (lambda (consequent alternate) (funcall alternate))  ;; false

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Kalle Olavi Niemitalo
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <878y74gb6a.fsf@Astalo.kon.iki.fi>
····@rpw3.org (Rob Warnock) writes:

> But BLOCK, TAGBODY, GO, UNWIND-PROTECT, MULTIPLE-VALUE-CALL, RETURN,
> RETURN-FROM, etc., I dunno.

RETURN can obviously be expanded to RETURN-FROM.

TAGBODY and GO can be implemented with BLOCK and RETURN-FROM.
I have done that in Emacs Lisp, with lexical scoping.

BLOCK and RETURN-FROM can be implemented with THROW and CATCH,
although that will cons.  Emacs Lisp does that, but its
interpreter gets the scope wrong.

All non-local exits will then ultimately call THROW, and if you
implement that suitably, UNWIND-PROTECT can just push closures on
a stack.

MULTIPLE-VALUE-CALL needs to be special, I think.  Still, one
could cheat by moving the specialness into a function:

  (defmacro multiple-value-call (function-form &rest forms)
    `(multiple-value-call-with-thunks ,function-form
       ,@(mapcar #'(lambda (form) `#'(lambda () ,form)) forms)))

That would get rid of one special form, but I suppose it would be
even harder to implement, and slower to execute.

> And then all the declaration stuff -- DECLAIM, DECLARE,
> LOCALLY, THE -- those are pretty "special" operators.

DECLAIM is already specified to be a macro.

How about this for THE:

  (defmacro the (value-type form)
    (let ((result (gensym)))
      `(let ((,result ,form))
         (declare (type ,value-type ,result))
         ,result)))

That does the right thing for single-valued forms, I think.
Multiple values could almost be supported by converting e.g.
(the (values a b &rest c) (d)) to the following:

  (destructuring-bind (&whole g1 &optional g2 g3 &rest g4)
      (multiple-value-list (d))
    ;; It would be nice to declare dynamic-extent for the conses
    ;; in the cdr chain of g1, but I don't think that can be done
    ;; without making the elements dynamic-extent as well.
    (declare (type a g2)
             (type b g3))  ;; How to declare g4 is a list of c?
    (case (length g1)
      (0 (values))
      (1 (values g2))
      (2 (values g2 g3))
      (t (apply #'values g2 g3 g4))))
From: Barry Margolin
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <barmar-A3ED2A.17421407012005@comcast.dca.giganews.com>
In article <··············@Astalo.kon.iki.fi>,
 Kalle Olavi Niemitalo <···@iki.fi> wrote:

> BLOCK and RETURN-FROM can be implemented with THROW and CATCH,
> although that will cons.  Emacs Lisp does that, but its
> interpreter gets the scope wrong.

Isn't that an inherent problem of that translation?  CATCH/THROW is 
dynamic, BLOCK/RETURN-FROM is lexical, so can they really be defined in 
terms of each other?

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: Edi Weitz
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <ud5wg26o5.fsf@agharta.de>
On Fri, 07 Jan 2005 17:42:14 -0500, Barry Margolin <······@alum.mit.edu> wrote:

> Isn't that an inherent problem of that translation?  CATCH/THROW is
> dynamic, BLOCK/RETURN-FROM is lexical, so can they really be defined
> in terms of each other?

  "We will show that only one of the three non-local exit mechanisms
   block/return-from, tagbody/go, catch/throw is required to be
   primitive, by showing how to emulate any two in terms of the
   third."

<http://home.pipeline.com/~hbaker1/MetaCircular.html>

Edi.

-- 

Lisp is not dead, it just smells funny.

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: drewc
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <3VHDd.5554$6l.5281@pd7tw2no>
Edi Weitz wrote:

> 
>   "We will show that only one of the three non-local exit mechanisms
>    block/return-from, tagbody/go, catch/throw is required to be
>    primitive, by showing how to emulate any two in terms of the
>    third."
> 
> <http://home.pipeline.com/~hbaker1/MetaCircular.html>
> 
> Edi.

Great article Edi, thanks for the pointer. Reminds me of Lambda the 
Ultimate *, only using Common Lisp (ie: IF in terms of lamdba, etc).

Particularly interesting is the following :

"we feel that the Common Lisp "macro" is the santioned mechanism for 
adding new "special forms". While this view of special forms is not 
evident from CLtL2 [Steele90], it should be obvious by the end of this 
paper. In short, the choice of which "macros" are "special forms" is 
just as arbitrary as the choice of a axes in a coordinate system for the 
Cartesian X-Y plane--e.g., some sets of macros are "linearly 
independent", and some sets of macros "span" the space of special forms."

I think this is the view the OP was getting at, that most special forms 
are simply macros. Of course, we do need a few primative special 
forms/functions in lisp, but in common lisp, what is a special form vs a 
macro is an arbitrary implementation issue.

I've just started my studies of LtU, and i find it quite fascinating. 
Coming from a C point of view, the ability to define everything in terms 
of lambda blows my mind. And then to do it all without a stack! wow.

drewc
From: Barry Margolin
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <barmar-4B9221.01114608012005@comcast.dca.giganews.com>
In article <··················@pd7tw2no>, drewc <·····@rift.com> wrote:

> I think this is the view the OP was getting at, that most special forms 
> are simply macros. Of course, we do need a few primative special 
> forms/functions in lisp, but in common lisp, what is a special form vs a 
> macro is an arbitrary implementation issue.

True.  In one of my first responses in the thread, I was careful to say 
that the special forms are ones that are not *easy* to implement in 
terms of other primitives.  While it may be possible, the resulting code 
is likely to be difficult to compile well.

The list of special forms in the language spec is the result of 
experienced language designers and implementors, who know which 
operators typically need to be recognized as primitives by the 
implementation.  The spec also says that an implementation is allowed to 
implement any special operator as a macro.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: Rob Warnock
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <bbadnYSk5PeTmXzcRVn-tQ@speakeasy.net>
[Barry knows this, but just for completeness...]

Barry Margolin  <······@alum.mit.edu> wrote:
+---------------
| The list of special forms in the language spec is the result of 
| experienced language designers and implementors, who know which 
| operators typically need to be recognized as primitives by the 
| implementation.  The spec also says that an implementation is
| allowed to implement any special operator as a macro.
+---------------

And vice-versa [2nd sentence below], with one additional proviso:

    3.1.2.1.2.2 Macro Forms
    ...
    An implementation is free to implement a Common Lisp special
    operator as a macro. An implementation is free to implement
    any macro operator as a special operator, but only if an
    equivalent definition of the macro is also provided.

Presumably this is so that user-written code-walkers that don't
know that some macro is really a special operator in a particular
implementation can still call MACROEXPAND and do (almost) the
right thing.


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Barry Margolin
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <barmar-B186DB.20160006012005@comcast.dca.giganews.com>
In article <··············@sidious.geddis.org>,
 Don Geddis <···@geddis.org> wrote:

> M Jared Finder <·······@digipen.edu> wrote on Wed, 05 Jan 2005:
> > The important thing here is that the set of symbols that are special
> > operators are *fixed*.  This allows you to look at any Lisp form and know
> > what subforms could be evaluated and which can't.  This is useful if you 
> > want
> > to write EVAL as a Lisp function.
> 
> I'm not sure how this helps me.  Surely whatever special casing you need
> to do for special operators, you also need to do for macros.
> 
> Or are you saying that in order to write EVAL, you actually have to
> _implement_ all the special operators within your code, but you can simply
> FUNCALL the functions, and MACROEXPAND the macros?
> 
> Yet it would seem that you wouldn't need this distinction, if CL's
> special operators had been specified to be macros also.

What would they expand into?  Eventually you have to get something 
primitive that the interpreter must process directly.

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
From: Harald Hanche-Olsen
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <pcosm5fa1og.fsf@shuttle.math.ntnu.no>
+ Don Geddis <···@geddis.org>:

| What is the difference between special forms and macros in Common Lisp?

Check the HyperSpec.  It has a quite useful glossary.  Briefly put,
macro forms expand into other forms.

| Assume that I have a list of a few special forms and a few macros.
| Presumably there is some (portable) CL function you can write to
| tell the difference, and tell me how many items in my list are
| special forms and how many are macros.

Look up macro-functions and special-operator-p.

| Is one concept a subset of the other?

No, they are disjoint by definition.  See "special form" in the CLHS
Glossary.

| Is there some property that every special form must have, but
| macros are not required to have?  Or vis versa?

Macros can be expanded, special forms cannot.

| I guess the real question is, why did the ANSI committee invent this
| concept of "special forms"?  How is the ANSI CL standard stronger
| because that concept exists (as distinct from macros)?

Think of all the things you could not do without special forms:
Defining functions, binding variables, ...  Since macros by definition
expand into other forms, they cannot in the final analysis do the
job on their own.

It might be interesting to learn something about how special forms
evolved out of earlier concepts, though.  I remember stumbling across
a LISP manual ages ago, long before Common Lisp, and being confused by
the profusion of different sorts of functions with different rules for
evaluating arguments.  The present situation is surely a lot easier to
understand.

-- 
* Harald Hanche-Olsen     <URL:http://www.math.ntnu.no/~hanche/>
- Debating gives most of us much more psychological satisfaction
  than thinking does: but it deprives us of whatever chance there is
  of getting closer to the truth.  -- C.P. Snow
From: Peter Seibel
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <m34qhv30pz.fsf@javamonkey.com>
Harald Hanche-Olsen <······@math.ntnu.no> writes:

> + Don Geddis <···@geddis.org>:
>
> | What is the difference between special forms and macros in Common
> | Lisp?

[snip]

> Think of all the things you could not do without special forms:
> Defining functions, binding variables, ... Since macros by
> definition expand into other forms, they cannot in the final
> analysis do the job on their own.

Or for a completely different way to approach this same topic, check
out these two chapters from my book.

  <http://www.gigamonkeys.com/book/practical-an-html-generation-library-the-interpreter.html>
  <http://www.gigamonkeys.com/book/practical-an-html-generation-library-the-compiler.html>

While ostensibly about yet another HTML generation library, it's
really about how to develop a domain specific language and one that
happens to have its own macros and special operators. While I don't
explicitly tie it back to Common Lisp, if you read this and see the
distinction that exists between special operators and macros in this
language it may shed some light on the distinction in Common Lisp.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Don Geddis
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <878y76ct1p.fsf@sidious.geddis.org>
Peter Seibel <·····@javamonkey.com> wrote on Wed, 05 Jan 2005:
> Or for a completely different way to approach this same topic, check
> out these two chapters from my book.
>   <http://www.gigamonkeys.com/book/practical-an-html-generation-library-the-interpreter.html>
>   <http://www.gigamonkeys.com/book/practical-an-html-generation-library-the-compiler.html>
> While ostensibly about yet another HTML generation library, it's
> really about how to develop a domain specific language and one that
> happens to have its own macros and special operators. While I don't
> explicitly tie it back to Common Lisp, if you read this and see the
> distinction that exists between special operators and macros in this
> language it may shed some light on the distinction in Common Lisp.

Sorry, no, that didn't help (or perhaps I missed it).

It's a clever chapter, and I enjoyed the domain and discussion.  And you
did make your macros and special-forms different, in the sense that you
developed two flavors of macros, so your macro implementation is more complex
than your special form implementation.

But since you described special forms first, I never got the motivation for
why you needed them if you had already had macros!  (I don't disagree with
your exposition order; most of your readers probably don't have the specific
concern I've raised in this thread.)

I understand that you did develop two concepts, and you implemented them
separately.  But what I'm missing is, what goes wrong if you merge the
concepts?  Why not only have macros, and then implement your handful of
special operators as macros?

        -- Don

P.S. In the middle of the compiler page, you have
        (:p (:if (zerop (random 2))) "Heads" "Tails")
which I think should have parens like this instead:
        (:p (:if (zerop (random 2)) "Heads" "Tails"))
Similarly for the next line of code.  Unless I'm really confused.
_______________________________________________________________________________
Don Geddis                  http://don.geddis.org/               ···@geddis.org
A good thing to do, if you have a lot of time, is walk up behind people on the
street, tap them on the shoulder, and when they turn around, see if you know
them.
	-- Deep Thoughts, by Jack Handey [1999]
From: Peter Seibel
Subject: Re: Special forms vs. Macros
Date: 
Message-ID: <m3ekgyz7eo.fsf@javamonkey.com>
Don Geddis <···@geddis.org> writes:

> Peter Seibel <·····@javamonkey.com> wrote on Wed, 05 Jan 2005:
>> Or for a completely different way to approach this same topic, check
>> out these two chapters from my book.
>>   <http://www.gigamonkeys.com/book/practical-an-html-generation-library-the-interpreter.html>
>>   <http://www.gigamonkeys.com/book/practical-an-html-generation-library-the-compiler.html>
>> While ostensibly about yet another HTML generation library, it's
>> really about how to develop a domain specific language and one that
>> happens to have its own macros and special operators. While I don't
>> explicitly tie it back to Common Lisp, if you read this and see the
>> distinction that exists between special operators and macros in this
>> language it may shed some light on the distinction in Common Lisp.
>
> Sorry, no, that didn't help (or perhaps I missed it).
>
> It's a clever chapter, and I enjoyed the domain and discussion. And
> you did make your macros and special-forms different, in the sense
> that you developed two flavors of macros, so your macro
> implementation is more complex than your special form
> implementation.
>
> But since you described special forms first, I never got the
> motivation for why you needed them if you had already had macros! (I
> don't disagree with your exposition order; most of your readers
> probably don't have the specific concern I've raised in this
> thread.)
>
> I understand that you did develop two concepts, and you implemented
> them separately. But what I'm missing is, what goes wrong if you
> merge the concepts? Why not only have macros, and then implement
> your handful of special operators as macros?

The problem is that macros can only expand into things the language
processor understands. Without special operators that would be--in
this case--only s-expression HTML and other macros. There's no way to
write a macro that does what, for instance, the :noescape special
operator does because binding the *escapes* variable is part of the
underlying language processor--in the compiler it happens at compile
time.

> P.S. In the middle of the compiler page, you have
>         (:p (:if (zerop (random 2))) "Heads" "Tails")
> which I think should have parens like this instead:
>         (:p (:if (zerop (random 2)) "Heads" "Tails"))
> Similarly for the next line of code.  Unless I'm really confused.

Nope, that's a bug. Fixed now. Thanks.

-Peter

-- 
Peter Seibel                                      ·····@javamonkey.com

         Lisp is the red pill. -- John Fraser, comp.lang.lisp