From: Kevin Clancy
Subject: Paul Graham's teaching style is bad
Date: 
Message-ID: <10hq6alqdpo4404@corp.supernews.com>
On Lisp - 7.1
"Many languages offer some form of macro, but Lisp macros are singularly
powerful. When a file of Lisp is compiled, a parser reads the source code
and sends its output to the compiler. Here's the stroke of genius: the ouput
of the parser consists of lists of Lisp objects. With macros, we can
manipulate the program while it's in this intermidiate form between parser
and compiler."

Gee. What a revelation. After about a half hour of contemplation, I came to
the conclusion that what he was trying to say was that you can use Lisp to
program the preprocessor.

That's cool. Unfortunately, Graham's excitement did not carry over to me as
the reader. I have some sort of an intuitive idea of a Lisp object as
anything enclosed by a "(" and a ")", although I do not beleive that was
ever explicity stated in either "On Lisp" or Winston & Horn's book.

So at this point, I'm guessing that the advantage of Lisp macros only comes
when compilation takes places in the midst of your program... I'm confused.

What I need is a more detailed explanation. Obviously, since Graham isn't
telling the reader everything that he knows, can anyone point me to some
resources that Graham may have used to gain his unrestrainable enthusiasm
for this language?

Thanks in advance,
Kevin

From: Jock Cooper
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <m3vffmvdoe.fsf@jcooper02.sagepub.com>
"Kevin Clancy" <············@hotmail.com> writes:

> On Lisp - 7.1
> "Many languages offer some form of macro, but Lisp macros are singularly
> powerful. When a file of Lisp is compiled, a parser reads the source code
> and sends its output to the compiler. Here's the stroke of genius: the ouput
> of the parser consists of lists of Lisp objects. With macros, we can
> manipulate the program while it's in this intermidiate form between parser
> and compiler."
> 
> Gee. What a revelation. After about a half hour of contemplation, I came to
> the conclusion that what he was trying to say was that you can use Lisp to
> program the preprocessor.
> 
> That's cool. Unfortunately, Graham's excitement did not carry over to me as
> the reader. I have some sort of an intuitive idea of a Lisp object as
> anything enclosed by a "(" and a ")", although I do not beleive that was
> ever explicity stated in either "On Lisp" or Winston & Horn's book.
> 
> So at this point, I'm guessing that the advantage of Lisp macros only comes
> when compilation takes places in the midst of your program... I'm confused.
> 
> What I need is a more detailed explanation. Obviously, since Graham isn't
> telling the reader everything that he knows, can anyone point me to some
> resources that Graham may have used to gain his unrestrainable enthusiasm
> for this language?
> 


With a macro you can abstract certain types of code that aren't
possible or are awkward using functions.

For example, suppose you have some web code that looks like this:

(let ((name (get-value html-query "name"))
      (addr-1 (get-value html-query "addr_1"))
      (addr-2 (get-value html-query "addr_2"))
      (city (get-value html-query "city"))
      (state (get-value html-query "state"))
      (postal-code (get-value html-query "postal_code")))
    ...some code...
)

Using a macro you could write thusly:

(with-form-values (name addr-1 addr-2 city state postal-code) html-query
   ... some code ...
)

The macro can take the second form and transform it into the first
automagically.

This is a really simple example, but it makes for cleaner code.  You
can 'hide' the scaffolding code you have to write repeatedly.  Yes
functions will serve for much of this, but not always.

A macro also allows computation to happen at compile time rather than
runtime.  

Something along the lines of:

(define-parser %parse ((open "(") (close ")"))
    ((a-list . ((%open items %close) $2))
     ((item :plural t) . ((something) $1))
     (something . (or 
		   ((%ident) $1)
		   ((%string) $1)))))
           
which a macro can transform into (apologies for the length, I'm trying
to show a less trivial example):

(DEFUN %PARSE (#:G3862)
 (LET* ((#:G3863 (PARSER::MAKE-TOKENS ((OPEN "(") (CLOSE ")"))))
     (#:G3864 (PARSER::LEXICAL-TOKENIZER #:G3862 #:G3863))
     (PARSER::*PARSE-TOKEN-LENGTH* (LENGTH #:G3864))
     (PARSER::*PARSE-POS* 0))
  (LABELS ((A-LIST ()
       (PARSER::PARSE-CHECK #:G3864
         (LIST '%OPEN #'ITEMS '%CLOSE)
         (SETQ PARSER::MATCHED
          (DESTRUCTURING-BIND
           (&OPTIONAL $1 $2 $3 $4 $5 $6 $7 $8 $9 $10)
            PARSER::MATCHED
         (DECLARE
          (IGNORABLE $1 $2 $3 $4 $5 $6 $7
          $8 $9 $10))
        $2))))
       (ITEMS ()
        (PARSER::MV-OR
        (PARSER::PARSE-CHECK #:G3864
           (LIST #'ITEM #'ITEMS)
           (SETQ PARSER::MATCHED
			  (DESTRUCTURING-BIND
				 (&OPTIONAL $1 $2 $3 $4 $5 $6
					  $7 $8 $9 $10)
			    PARSER::MATCHED
			   (DECLARE
			   (IGNORABLE $1 $2 $3 $4 $5 $6 $7
					 $8 $9 $10))
			   (CONS $1 $2))))
        (PARSER::PARSE-CHECK #:G3864 (LIST #'ITEM))))
       (ITEM ()
        (PARSER::PARSE-CHECK #:G3864
          (LIST #'SOMETHING)
		  (SETQ PARSER::MATCHED
			 (DESTRUCTURING-BIND
				(&OPTIONAL $1 $2 $3 $4 $5 $6 $7
					  $8 $9 $10)
			   PARSER::MATCHED
			  (DECLARE
			   (IGNORABLE $1 $2 $3 $4 $5 $6 $7
					$8 $9 $10))
			  $1))))
       (SOMETHING ()
         (PARSER::MV-OR
           (PARSER::PARSE-CHECK #:G3864
             (LIST '%IDENT)
                   (SETQ PARSER::MATCHED
                       (DESTRUCTURING-BIND
                         (&OPTIONAL $1 $2 $3 $4 $5 $6
                         $7 $8 $9 $10)
                         PARSER::MATCHED
                        (DECLARE
                        (IGNORABLE $1 $2 $3 $4 $5 $6 $7
                         $8 $9 $10))
                        $1)))
           (PARSER::PARSE-CHECK #:G3864
             (LIST '%STRING)
                  (SETQ PARSER::MATCHED
                       (DESTRUCTURING-BIND
                         (&OPTIONAL $1 $2 $3 $4 $5 $6
                         $7 $8 $9 $10)
                         PARSER::MATCHED
                        (DECLARE
                        (IGNORABLE $1 $2 $3 $4 $5 $6 $7
                         $8 $9 $10))
                        $1))))))

   (LET ((PARSER::*PARSE-PROGRESS* NIL))
    (MULTIPLE-VALUE-BIND
      (PARSER::MATCHP PARSER::MATCHED)
      (A-LIST)
     (UNLESS (EQUAL #:G3864 PARSER::*PARSE-PROGRESS*)
      (LET*
	  ((PARSER::FULL-STREAM
	    (PARSER::DETOKENIZER #:G3864 #:G3863))
          (PARSER::PROGRESS-STREAM
          (PARSER::DETOKENIZER PARSER::*PARSE-PROGRESS* #:G3863))
          (POSITION (LENGTH PARSER::PROGRESS-STREAM))
          (PARSER::BEFORE (MIN 40 POSITION))
          (PARSER::AFTER
          (MIN 40 (- (LENGTH PARSER::FULL-STREAM) POSITION)))
          (PARSER::DESC
          (WITH-OUTPUT-TO-STRING (*STANDARD-OUTPUT*)
           (FORMAT T
               "Token stream: ~a ##ERROR## ~a~%"
               (SUBSEQ PARSER::FULL-STREAM
                   (- POSITION PARSER::BEFORE)
                   POSITION)
               (SUBSEQ PARSER::FULL-STREAM
                   POSITION
                   (+ POSITION PARSER::AFTER)))
           (FORMAT T "Error location is approximate.~%"))))
       (ERROR 'PARSE-FAILURE
           :DESC
           PARSER::DESC
           :PARTIAL
           (IF PARSER::MATCHP PARSER::MATCHED NIL))))
     (IF PARSER::MATCHP
       (VALUES PARSER::MATCHP PARSER::MATCHED)
       (VALUES NIL NIL)))))))

--
Jock Cooper
http://www.fractal-recursions.com




      
From: Joe Marshall
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <fz6qkct8.fsf@ccs.neu.edu>
"Kevin Clancy" <············@hotmail.com> writes:

> After about a half hour of contemplation, I came to the conclusion
> that what he was trying to say was that you can use Lisp to program
> the preprocessor.

Not exactly.  In Lisp, the macro essentially acts on the abstract
syntax tree, not the raw tokens.  So you can use Lisp to program the
front end of the compiler.  This is a bit more powerful than just a
preprocessor.

(To be more precise, the reason this works so well is because the
abstract syntax and the concrete syntax for lisp is trivially
isomorphic.)
From: Peter Seibel
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <m3ekma6awl.fsf@javamonkey.com>
"Kevin Clancy" <············@hotmail.com> writes:

> What I need is a more detailed explanation. Obviously, since Graham
> isn't telling the reader everything that he knows, can anyone point
> me to some resources that Graham may have used to gain his
> unrestrainable enthusiasm for this language?

Well he didn't use this resource since it didn't exist until recently
but I'm at work on a book about Common Lisp which you might
useful--it's written for folks who already know how to program in some
other language and have heard enough about Lisp to be curious what
folks like Graham *are* going on about. I have the chapters I've
finished so far up for review at:

  <http://www.gigamonkeys.com/book/>

You'll probably be particularly interested in chapters 7 and 8 which
cover macros. If you have any feedback I'd love to hear it as you seem
to be pretty good representative of my target reader.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Peter Herth
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <cfj6gr$fic$1@newsreader2.netcologne.de>
Kevin Clancy wrote:

> On Lisp - 7.1
> "Many languages offer some form of macro, but Lisp macros are singularly
> powerful. When a file of Lisp is compiled, a parser reads the source code
> and sends its output to the compiler. Here's the stroke of genius: the
> ouput of the parser consists of lists of Lisp objects. With macros, we can
> manipulate the program while it's in this intermidiate form between parser
> and compiler."
[-]
> 
> What I need is a more detailed explanation. Obviously, since Graham isn't
> telling the reader everything that he knows, can anyone point me to some
> resources that Graham may have used to gain his unrestrainable enthusiasm
> for this language?

Well, what Paul Graham says is exactly the thing. Between reading a Lisp
program and compiling it, there is a stage where you have the code parsed
into data structures accessably from your Lisp code (actually using lists,
the most versatile data structure in Lisp). So via macros you can have
your own code run at this stage and thus essentially write program-writing
programs. But while you can write preprocessors in any language, in Lisp
this is especially well integrated.

Peter

-- 
pet project: http://dawn.netcologne.de
homepage:    http://www.peter-herth.de
lisp stuff:  http://www.peter-herth.de/lisp.html
get Ltk here: http://www.peter-herth.de/ltk/
From: Kevin Clancy
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <10hqhua4rbsgb26@corp.supernews.com>
I just realized that Graham actually visits this newsgroup. If I had known
that, I would never have given this thread such a tactless title.

I actually like how "On Lisp" uses real world examples. Perhaps my real
problem is that my first Lisp book, Winston & Horn, was inadequate.

-Kevin
From: Wade Humeniuk
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <oQaTc.10813$jZ5.4336@clgrps13>
Kevin Clancy wrote:

> What I need is a more detailed explanation. Obviously, since Graham isn't
> telling the reader everything that he knows, can anyone point me to some
> resources that Graham may have used to gain his unrestrainable enthusiasm
> for this language?

Why using an implementation of the language itself is the resource.  That
and enough programming experience to understand why being able
to extend the compiler by using macros is useful.  It invariably
seems when an application gets complex enough then a "expert
language" is built to allow more efficient and expressive code
writing.  An example would be computer games where scenes and
characters are coded with specialized languages.  In Lisp the
specialized language can be written in macros. Other languages
usuaully have to write parsers/preprocessors/interpreters/compilers to handle
the higher level language.  In Lisp, you can create a expert language
by creating macros utilizing the inherent flexibility of sexps.
The key here is to give yourself over to the syntaxless simplicity of
Lisp s-expressions.

Wade
From: Matthew Danish
Subject: Re: Is Lisp "syntaxless"? (was: Paul Graham's teaching style is bad)
Date: 
Message-ID: <20040813225554.GO15746@mapcar.org>
On Fri, Aug 13, 2004 at 10:24:04PM +0000, Stefan Ram wrote:
> Wade Humeniuk <····································@telus.net> writes:
> >The key here is to give yourself over to the syntaxless
> >simplicity of Lisp s-expressions.
> 
>   A pure s-expression would be something being described by the
>   ENBF production
> 
> <s-expression> ::= <atom> | "(" { <s-expression> } ")"
> 
>   As long as the structure inside the parentheses consists only
>   of the sequence { <s-expression> }, we can arrange to call
>   that "syntaxless". 
> 
>   But in Common Lisp, e.g., the loop structure, as being
>   described by, e.g.,
> 
> http://www.cs.washington.edu/ai/cltl/clm/node241.html
> 
>   seems to have much more syntax, than just { <s-expression> }
>   inside the parentheses.

But, in fact, the LOOP macro is still an s-expression.  Personally, I
wouldn't call Lisp "syntaxless" as that is somewhat extreme.  As you
have noticed, there is a level of syntax to Lisp that describes
s-expressions that is fairly simple.  This level simply maps into Lisp
data-structures which represent the underlying "abstract" syntax tree
(not so abstract for Lisp).  Now, at this "abstract" syntax level, there
is a great deal of variation; often operator-dependent, as with the LOOP
macro.

The real advantage and beauty of Lisp code is the (relatively) simple
mapping of the print representation to the internal representation, and
the easy manipulation and inspection of that internal representation.
In this way can Lisp be said to be nearly syntaxless; no matter the
meaning of the operators, the Lisp reader still performs the same simple
job.

-- 
;;;; Matthew Danish -- user: mrd domain: cmu.edu
;;;; OpenPGP public key: C24B6010 on keyring.debian.org
From: Kaz Kylheku
Subject: Re: Is Lisp "syntaxless"? (was: Paul Graham's teaching style is bad)
Date: 
Message-ID: <cf333042.0408170957.14aa3d72@posting.google.com>
Matthew Danish <·······@andrew.cmu.edu> wrote in message news:<······················@mapcar.org>...
> On Fri, Aug 13, 2004 at 10:24:04PM +0000, Stefan Ram wrote:
> > Wade Humeniuk <····································@telus.net> writes:
> > >The key here is to give yourself over to the syntaxless
> > >simplicity of Lisp s-expressions.
> > 
> >   A pure s-expression would be something being described by the
> >   ENBF production
> > 
> > <s-expression> ::= <atom> | "(" { <s-expression> } ")"
> > 
> >   As long as the structure inside the parentheses consists only
> >   of the sequence { <s-expression> }, we can arrange to call
> >   that "syntaxless". 
> > 
> >   But in Common Lisp, e.g., the loop structure, as being
> >   described by, e.g.,
> > 
> > http://www.cs.washington.edu/ai/cltl/clm/node241.html
> > 
> >   seems to have much more syntax, than just { <s-expression> }
> >   inside the parentheses.
> 
> But, in fact, the LOOP macro is still an s-expression.  Personally, I
> wouldn't call Lisp "syntaxless" as that is somewhat extreme.

Lisp isn't syntaxless, but rather has a read syntax which is
comparable in complexity to the lexical syntax of other languages. In
roughtly the amount of complexity that is merely required to break the
source code of some languages into a string of tokens, Lisp produces
an abstract syntax tree.

What is missing from Lisp is the next lexical syntax stage, which has
to make sense out of a raw stream of tokens and turn them into an
abstract syntax tree according to some grammar.

This is what we mean when we say that Lisp is syntaxless: that it
doesn't have the conventional syntactic analysis stage where a
hard-wired, inflexible phrase structure rules act upon a token stream.

Because Lisp doesn't have this stage, the Lisp compiler never has to
actually parse anything; the output of the lexical analyzer can be
directly subjected to tree-walking, something that can only be done in
conventional languages after the syntactic parse.

There are parsing tasks to be done, but when they are done by tree
walking, it's very different. You don't need a complicated state
machine to just recognize which kind of phrase you are looking at; you
get that by considering the symbol, and then validating the shape of
the remaining tree to see that it has the right shape for that lexical
category. You can pull out the pieces you need by position! For other
languages, people write tools like Yacc just to be able to do this: to
write a programming action associated with a phrase structure rule,
where the action can use simple positional access to retrieve the
constituent phrases.

In essence, Lisp goes just about directly from trivial lexical
processing into what, traditionally, is considered to belong in the
domain of semantic analysis. In traditional compiler design theory,
parsing syntax is done when a tree shape pops out. Parsing is that
activity that you have to do so that you end up with a representation
in which you can directly access, say, the third child of some node
and easily validate that it's, say, a constant expression of integer
type.

Nobody outside of Lisp (and maybe linguistics) considers syntax
processing to be the actions taken on a nice, shiny tree structure.
Rather, syntax is that self-imposed torture that one must overcome to
get to that nice stage.

Any constraints that are checked after difficult labor of giving birth
to the tree are no longer considered to be syntax, but semantics. Of
course, in the Lisp world, we know better, but in the language of the
rest of the computing world, to say that Lisp is syntaxless is quite
accurate: it's free of the torture that fills the pages of the Red
Dragon Book, and on which you can base an entire tortuous one-semester
CS course whose final exam has questions like ``identify the LR(0)
items in this grammar and produce the LALR(1) transition table''.

> The real advantage and beauty of Lisp code is the (relatively) simple
> mapping of the print representation to the internal representation, and
> the easy manipulation and inspection of that internal representation.
> In this way can Lisp be said to be nearly syntaxless; no matter the
> meaning of the operators, the Lisp reader still performs the same simple
> job.

Quite similarly, the tokenizer for Pascal can also recognize any valid
stream of Pascal tokens without error, even if the syntax is nonsense.
One big useless list of items pops out, rather than a nice nested
list.

The Forth language is an interesting case. It also starts with a flat
list of tokens, but their syntax is analyzed implicitly as part of the
evaluation semantics of the program. Certain words cause items to be
removed from a stack, and other items to be put back on the stack.
Thus the program acts as a kind of shift-reduce parser, using its
evaluation stack to give a shape to the flat stream of words. Again,
this language is called syntaxless, but it's not quite accurate.
Again, it just means that there isn't a grammar acting on the stream
of tokens, but in this case, the tokens act on themselves in a
structured way.
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: Is Lisp "syntaxless"? (was: Paul Graham's teaching style is bad)
Date: 
Message-ID: <pan.2004.08.17.21.19.00.151389@knm.org.pl>
On Tue, 17 Aug 2004 10:57:13 -0700, Kaz Kylheku wrote:

> Lisp isn't syntaxless, but rather has a read syntax which is
> comparable in complexity to the lexical syntax of other languages.

Really?

clisp-2.33.2/src/io.d                  185 kB
  (after manually removing the printer, leaving only the reader)
cmucl-183.source/src/code/reader.lisp   53 kB
sbcl-0.8.5/src/code/reader.lisp         54 kB

fpc-0.99.14/compiler/scanner.pas        53 kB
gwydion-dylan-2.3.11/mindy/comp/lexer.l  7 kB
ghc-6.3/compiler/parser/Lexer.x         38 kB
hugs98-Dec2001/src/input.c              62 kB
mosml-2.00/src/lex/Scanner.lex           3 kB
ocaml-3.08.0/lex/lexer.mll               8 kB
perl-5.8.5/toke.c                      207 kB
Python-2.3.4/Parser/tokenizer.c         30 kB
smlnj-110.0.7/sml-nj/lex/ml.lex         12 kB
smalltalk-1.95.1/libgst/lex.c           38 kB

Unfortunately I don't have sources of other Lisp implementations here to
compare.

Yes, it's simpler than Perl. Everything else I know of has a simpler
lexical structure than Perl.

> What is missing from Lisp is the next lexical syntax stage, which has
> to make sense out of a raw stream of tokens and turn them into an
> abstract syntax tree according to some grammar.

Yes. Half of this is done by the reader, the other half by particular
special forms and macros which have their own little grammars.

It has a different split into stages than most languages, but it doesn't
make it simpler.

> This is what we mean when we say that Lisp is syntaxless: that it
> doesn't have the conventional syntactic analysis stage where a
> hard-wired, inflexible phrase structure rules act upon a token stream.

Yes, it's more flexible, but not simpler.

> Because Lisp doesn't have this stage, the Lisp compiler never has to
> actually parse anything; the output of the lexical analyzer can be
> directly subjected to tree-walking, something that can only be done in
> conventional languages after the syntactic parse.

The reader parses the source to an intermediate form. Particular special
forms and macros continue the parsing.

> There are parsing tasks to be done, but when they are done by tree
> walking, it's very different. You don't need a complicated state
> machine to just recognize which kind of phrase you are looking at; you
> get that by considering the symbol, and then validating the shape of
> the remaining tree to see that it has the right shape for that lexical
> category.

Unless you are parsing LOOP.

sbcl-0.8.5/src/code/loop.lisp  77kB

Yes, it also does part of code generation. I said that the phases are
split at different points. It doesn't make them smaller though.

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Thomas Schilling
Subject: Re: Is Lisp "syntaxless"? (was: Paul Graham's teaching style is bad)
Date: 
Message-ID: <opscwe11zxtrs3c0@news.CIS.DFN.DE>
Kaz Kylheku <···@ashi.footprints.net> wrote:

> Any constraints that are checked after difficult labor of giving birth
> to the tree are no longer considered to be syntax, but semantics. Of
> course, in the Lisp world, we know better, but in the language of the
> rest of the computing world, to say that Lisp is syntaxless is quite
> accurate: it's free of the torture that fills the pages of the Red
> Dragon Book, and on which you can base an entire tortuous one-semester
> CS course whose final exam has questions like ``identify the LR(0)
> items in this grammar and produce the LALR(1) transition table''.

Hm, haven't had this exam yet. ;)

But don't forget: Lisp also has a (assumedly) stack-based LALR(1) parser, 
though more often called a tokenizer - to read a symbol/number/string from 
the input string you still need a (quite complex) parser, though it's 
still quite customizable (reader-macros) and working fully behind the 
scenes.

And everyone who has ever tried to do anything serious with bison/yacc 
will esteem Lisp's easy syntax.

-ts
-- 
      ,,
     \../   /  <<< The LISP Effect
    |_\\ _==__
__ | |bb|   | _________________________________________________
From: Kenny Tilton
Subject: Re: Is Lisp "syntaxless"?
Date: 
Message-ID: <IshTc.95589$4h7.12616704@twister.nyc.rr.com>
Stefan Ram wrote:

> Wade Humeniuk <····································@telus.net> writes:
> 
>>The key here is to give yourself over to the syntaxless
>>simplicity of Lisp s-expressions.
> 
> 
>   A pure s-expression would be something being described by the
>   ENBF production
> 
> <s-expression> ::= <atom> | "(" { <s-expression> } ")"
> 
>   As long as the structure inside the parentheses consists only
>   of the sequence { <s-expression> }, we can arrange to call
>   that "syntaxless". 
> 
>   But in Common Lisp, e.g., the loop structure, as being
>   described by, e.g.,
> 
> http://www.cs.washington.edu/ai/cltl/clm/node241.html
> 
>   seems to have much more syntax, than just { <s-expression> }
>   inside the parentheses.

Now you know why LOOP is a tad controversial, and why Lisp macros are so 
cool: the syntax you observe comes from the authors of LOOP. It is not 
Lispy syntax. But Lisp macros can support any syntax their authors dream 
up. So Lisp can support non-Lispy syntax. How sick is that? :)

btw, LOOP can be authored with two syntaxes, one Lispy, one not. Scary, 
right? :)

kt

-- 
Cells? Cello? Celtik?: http://www.common-lisp.net/project/cells/
Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film
From: Bruce Hoult
Subject: Re: Is Lisp "syntaxless"?
Date: 
Message-ID: <bruce-896087.19340614082004@copper.ipg.tsnz.net>
In article <························@twister.nyc.rr.com>,
 Kenny Tilton <·······@nyc.rr.com> wrote:

> >   But in Common Lisp, e.g., the loop structure, as being
> >   described by, e.g.,
> > 
> > http://www.cs.washington.edu/ai/cltl/clm/node241.html
> > 
> >   seems to have much more syntax, than just { <s-expression> }
> >   inside the parentheses.
> 
> Now you know why LOOP is a tad controversial, and why Lisp macros are so 
> cool: the syntax you observe comes from the authors of LOOP. It is not 
> Lispy syntax. But Lisp macros can support any syntax their authors dream 
> up. So Lisp can support non-Lispy syntax. How sick is that? :)

I find it interesting that you can write macros such as LOOP in Common 
Lisp, but it provides no real support for the parsing of them, and if 
you want to put something not part of LOOP within a LOOP macro then it 
needs to go inside parenthesis.

Dylan can be looked at as providing built-in parsing support for 
LOOP-like macros that is good enough that there are a small number of 
primitives (literal, name, expression, block, function call) and 
everything else in the language is defined using macros.

Dylan's "for" loop is a macro and is very like LOOP, differing mainly in 
leaving out things such as COLLECT that can be done just as well with a 
separate facility (e.g. a "collecting" macro).

-- 
Bruce |  41.1670S | \  spoken |          -+-
Hoult | 174.8263E | /\ here.  | ----------O----------
From: Kenny Tilton
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <gPbTc.95559$4h7.12450456@twister.nyc.rr.com>
Kevin Clancy wrote:

> On Lisp - 7.1
> "Many languages offer some form of macro, but Lisp macros are singularly
> powerful. When a file of Lisp is compiled, a parser reads the source code
> and sends its output to the compiler. Here's the stroke of genius: the ouput
> of the parser consists of lists of Lisp objects. With macros, we can
> manipulate the program while it's in this intermidiate form between parser
> and compiler."
> 
> Gee. What a revelation. After about a half hour of contemplation, I came to
> the conclusion that what he was trying to say was that you can use Lisp to
> program the preprocessor.

Sounds like his teaching style worked.

> 
> That's cool. Unfortunately, Graham's excitement did not carry over to me as
> the reader.

(a) keep reading
(b) when the laser was invented no one knew what to do with it. They 
thought welding and weapons, but it was bad for both. never having had 
Lisp macros, you have no need for them. Now that you have Lisp macros, 
you will soon need them. for some ideas, see (a).

kt

-- 
Cells? Cello? Celtik?: http://www.common-lisp.net/project/cells/
Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film
From: Jock Cooper
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <m3r7qavcp8.fsf@jcooper02.sagepub.com>
Kenny Tilton <·······@nyc.rr.com> writes:

> Kevin Clancy wrote:
> 
> > On Lisp - 7.1
> > "Many languages offer some form of macro, but Lisp macros are singularly
> > powerful. When a file of Lisp is compiled, a parser reads the source code
> > and sends its output to the compiler. Here's the stroke of genius: the ouput
> > of the parser consists of lists of Lisp objects. With macros, we can
> > manipulate the program while it's in this intermidiate form between parser
> > and compiler."
> > Gee. What a revelation. After about a half hour of contemplation, I
> > came to
> > the conclusion that what he was trying to say was that you can use Lisp to
> > program the preprocessor.
> 
> Sounds like his teaching style worked.
> 
> > That's cool. Unfortunately, Graham's excitement did not carry over
> > to me as
> > the reader.
> 
> (a) keep reading
> (b) when the laser was invented no one knew what to do with it. They
> thought welding and weapons, but it was bad for both. never having had
> Lisp macros, you have no need for them. Now that you have Lisp macros,
> you will soon need them. for some ideas, see (a).
> 

Speaking of LASERs, I always found this popular old quote enlightening:

"For example in the past decade scientists have developed the laser,
an electronic appliance so powerful it can vaporize a bulldozer 2000
yards away, yet so precise that doctors can use it to perform delicate
operations to the human eyeball, provided they remember to change the
setting from 'bulldozer' to 'eyeball'"


-- 
Jock Cooper
http://www.fractal-recursions.com
From: Tayssir John Gabbour
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <866764be.0408132318.6cf3c57c@posting.google.com>
I agree; Paul Graham has written awesome things you don't find
anywhere else, but I didn't at all understand macros from his
writings. He seems to be more effective when you have certain concepts
down intuitively.

A macro merely takes one sexp (which we think of as "code") and
transforms it into another sexp. Ever notice how you don't perceive
sourcecode character-by-character? You mentally see it as symbols,
numbers, etc. Well, after lisp slurps in the characters of your
sourcecode and turns it into sexps, you can conveniently manipulate or
analyze this code just like any sort of data.

One place this is useful is to build a new control construct. Most
languages announce a new 'for' loop as if they're bringing fire from
the gods. In lisp, you simply create your 'for' macro and it can
transform your sexp into a sexp with gotos or a 'do' loop. I mean, a
'for' loop is so close to other loops in a language that there should
be a way to represent one as another, without having all the nuts &
bolts show.

It's just like you're making a user interface for programmers. Or for
yourself. Some people don't trust you to do this, but then how can
they trust you to program anything?


MfG,
Tayssir

--
Video, audio, and other lispish odds & ends
http://alu.cliki.net/Education
From: Peter Herth
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <cfkf9d$b4b$1@newsreader2.netcologne.de>
Tayssir John Gabbour wrote:

> One place this is useful is to build a new control construct. Most
> languages announce a new 'for' loop as if they're bringing fire from
> the gods. In lisp, you simply create your 'for' macro and it can
> transform your sexp into a sexp with gotos or a 'do' loop. I mean, a
> 'for' loop is so close to other loops in a language that there should
> be a way to represent one as another, without having all the nuts &
> bolts show.

Well, this is for me the prime example, whenever I try to explain
why Lisp is so different from other language in one sentence. 
I ask people how they would implement a looping construct like
"for" in their language. (For example repeat...until for C programmers).
In Lisp I can :) Acutally I implemented a C-style for for lisp, so for
those interested here it is. (it is actually in scheme (Kawa), but as it
uses defmacro and backquote the translation to Common Lisp should be
simple)

;; helper function

(define (for-expand defs body)
  (let ((def (car defs)))
    (if (list? def)
        (let ((rest-def (rest defs)))
          `(do ((,(first def) ,(second def) ,(fourth def)))
               ((not ,(third def)))
             ,(if (not (null? rest-def))
                  (for-expand rest-def body)
                  `(begin ,@body))))
          `(do ((,(first defs) ,(second defs) ,(fourth defs)))
               ((not ,(third defs)))
             ,@body))))

;; macro definition
(defmacro for (defs . body)
  (for-expand defs body))

;; sample usage, single loop
(define (test2)
  (for (i 0 (< i 10) (+ i 1))
       (display i)
       (newline)))

;; but it also enables any number of cascded loops with one construct,
;; here we iterate over a "cube" of numbers

(define (test3)
  (for ((i 0 (< i 5) (+ i 1))
        (j 2 (< j 7) (+ j 1))
        (k 3 (< k 5) (+ k 1)))
       (display i)
       (display " ")
       (display j)
       (display " ")
       (display k)
       (newline)))

Peter

-- 
pet project: http://dawn.netcologne.de
homepage:    http://www.peter-herth.de
lisp stuff:  http://www.peter-herth.de/lisp.html
get Ltk here: http://www.peter-herth.de/ltk/
From: Rainer Joswig
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <joswig-72AB92.12283714082004@news-50.dca.giganews.com>
In article <············@newsreader2.netcologne.de>,
 Peter Herth <·····@netcologne.de> wrote:

> Tayssir John Gabbour wrote:
> 
> > One place this is useful is to build a new control construct. Most
> > languages announce a new 'for' loop as if they're bringing fire from
> > the gods. In lisp, you simply create your 'for' macro and it can
> > transform your sexp into a sexp with gotos or a 'do' loop. I mean, a
> > 'for' loop is so close to other loops in a language that there should
> > be a way to represent one as another, without having all the nuts &
> > bolts show.
> 
> Well, this is for me the prime example, whenever I try to explain
> why Lisp is so different from other language in one sentence. 
> I ask people how they would implement a looping construct like
> "for" in their language. (For example repeat...until for C programmers).
> In Lisp I can :) Acutally I implemented a C-style for for lisp, so for
> those interested here it is. (it is actually in scheme (Kawa), but as it
> uses defmacro and backquote the translation to Common Lisp should be
> simple)
> 
> ;; helper function
> 
> (define (for-expand defs body)
>   (let ((def (car defs)))
>     (if (list? def)
>         (let ((rest-def (rest defs)))
>           `(do ((,(first def) ,(second def) ,(fourth def)))
>                ((not ,(third def)))
>              ,(if (not (null? rest-def))
>                   (for-expand rest-def body)
>                   `(begin ,@body))))
>           `(do ((,(first defs) ,(second defs) ,(fourth defs)))
>                ((not ,(third defs)))
>              ,@body))))

Which you might write in Common Lisp:

(defmacro for (defs &body body)
  (if (consp (first defs))
      (destructuring-bind ((var start test iteration) . rest-def) defs
        `(do ((,var ,start ,iteration))
             ((not ,test))
           ,@(if rest-def
                 `((for `,rest-def ,body))
               body)))
    `(for (,defs) ,@body)))

For a nice iteration facility see Jonathan Amsterdam's ITERATE
macro.

> 
> ;; macro definition
> (defmacro for (defs . body)
>   (for-expand defs body))
> 
> ;; sample usage, single loop
> (define (test2)
>   (for (i 0 (< i 10) (+ i 1))
>        (display i)
>        (newline)))
> 
> ;; but it also enables any number of cascded loops with one construct,
> ;; here we iterate over a "cube" of numbers
> 
> (define (test3)
>   (for ((i 0 (< i 5) (+ i 1))
>         (j 2 (< j 7) (+ j 1))
>         (k 3 (< k 5) (+ k 1)))
>        (display i)
>        (display " ")
>        (display j)
>        (display " ")
>        (display k)
>        (newline)))
> 
> Peter
From: Marco Parrone
Subject: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87k6w1by67.fsf_-_@marc0.dyndns.org>
Peter Herth on Sat, 14 Aug 2004 09:34:04 +0200 writes:

> Tayssir John Gabbour wrote:
>
>> One place this is useful is to build a new control construct. Most
>> languages announce a new 'for' loop as if they're bringing fire from
>> the gods. In lisp, you simply create your 'for' macro and it can
>> transform your sexp into a sexp with gotos or a 'do' loop. I mean, a
>> 'for' loop is so close to other loops in a language that there should
>> be a way to represent one as another, without having all the nuts &
>> bolts show.
>
> Well, this is for me the prime example, whenever I try to explain
> why Lisp is so different from other language in one sentence. 
> I ask people how they would implement a looping construct like
> "for" in their language. (For example repeat...until for C programmers).

Like this[1]?

Are you saying that's not possible to implement looping constructs in
other languages (like C), or that it is going to be done in a
different way?

1.

#include <stdio.h>

/* repeat .. until: implementation #1: aliasing do ... while */
/*
#define repeat do {
#define until } while
*/

/* repeat ... until: implementation #2: using GCC local labels */
/*
#define repeat { __label__ loop; loop:
#define until(cond) if (cond) goto loop; }
*/

/* repeat ... until: implementation #3: using GAS local labels */
#define repeat __asm__ ("1:");
#define until(cond) if (cond) __asm__ ("jmp 1b")

/* this allows 1 init, 1 body, 1 step. */
#define myfor(init, cond, step, body) { init; while (cond) { body; step; } }

/* this allows multiple init and body and step */
#define myfor2(init, cond, step, body) { init while (cond) { body step }} 


int
main (int argc, char *argv[])
{
  int i = 10;
  int j;
  int k;

  /*  the following expands to
  __asm__ ("1:");
    printf ("%d ", i);
    --i;
  if (i != 0) __asm__ ("jmp 1b");
  */

  repeat
    printf ("%d ", i);
    --i;
  until (i != 0);

  repeat
    printf ("%d ", i);
    ++i;
  until (i != 10);

  printf ("\n");

  /* the following expands to

  { j = 0; while (j < 10 && 1) { printf ("%d ", j); j++; } };
  */

  myfor (j = 0, j < 10 && 1, j++, printf ("%d ", j));

  printf ("\n");

  /* the following expands to

  { {j = 0; k = 0;} while (k*j < 20 && 1) { {printf ("[%d * %d = %d; %d] ", j, k, j*k, i); i++;} {j++; k += 3;} }};
  */

  myfor2 ({j = 0; k = 0;},
	  k*j < 20 && 1,
  {j++; k += 3;},
  {printf ("[%d * %d = %d; %d] ", j, k, j*k, i); i++;});


  printf ("\n");
  return 0;
}
From: Marco Parrone
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87d61tbw4y.fsf@marc0.dyndns.org>
Marco Parrone on Sat, 14 Aug 2004 14:22:26 GMT writes:

> /* this allows 1 init, 1 body, 1 step. */
> #define myfor(init, cond, step, body) { init; while (cond) { body; step; } }
>
> /* this allows multiple init and body and step */
> #define myfor2(init, cond, step, body) { init while (cond) { body step }} 

#define myfor2 myfor /* little uglier expansion, but works too */
From: Peter Seibel
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <m3hdr54u80.fsf@javamonkey.com>
Marco Parrone <·····@autistici.org> writes:

> Peter Herth on Sat, 14 Aug 2004 09:34:04 +0200 writes:
>
>> Tayssir John Gabbour wrote:
>>
>>> One place this is useful is to build a new control construct. Most
>>> languages announce a new 'for' loop as if they're bringing fire from
>>> the gods. In lisp, you simply create your 'for' macro and it can
>>> transform your sexp into a sexp with gotos or a 'do' loop. I mean, a
>>> 'for' loop is so close to other loops in a language that there should
>>> be a way to represent one as another, without having all the nuts &
>>> bolts show.
>>
>> Well, this is for me the prime example, whenever I try to explain
>> why Lisp is so different from other language in one sentence. 
>> I ask people how they would implement a looping construct like
>> "for" in their language. (For example repeat...until for C programmers).
>
> Like this[1]?
>
> Are you saying that's not possible to implement looping constructs
> in other languages (like C), or that it is going to be done in a
> different way?

I think he's saying it's in general not possible to implement new
control constructs in C. repeat/until is maybe not the best example to
challenge C programmers with because of solutions like yours. But
yours is still only a half solution since you are limited to textual
substitution:

  #include <stdio.h>

  #define repeat do {
  #define until } while

  int
  main (int argc, char *argv[])
  {
    int repeat = 10;

    repeat
      printf ("%d ", repeat);
      --repeat;
    until (repeat != 0);

    printf ("\n");
    return 0;
  }


  [·····@xeon peter]$ gcc foo.c
  foo.c: In function `main':
  foo.c:9: parse error before `do'
  foo.c:12: parse error before `do'
  foo.c:14: parse error before `do'
  foo.c:19: parse error at end of input
  [·····@xeon peter]$ 


But you could argue that this is really a lisp-1 vs lisp-2 problem. A
better example, I think, would be something like with_open_file. I
want to be able to write:

  with_open_file(in, "filename") {
    /* Do stuff with 'in' */
  }

and have it mean, open "filename" and make 'in' the variable holding
the stream and automatically close it when we reach the end of the
block.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Frank Buss
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <cfld3t$fn2$1@newsreader2.netcologne.de>
Peter Seibel <·····@javamonkey.com> wrote:

> But you could argue that this is really a lisp-1 vs lisp-2 problem. A
> better example, I think, would be something like with_open_file. I
> want to be able to write:
> 
>   with_open_file(in, "filename") {
>     /* Do stuff with 'in' */
>   }
> 
> and have it mean, open "filename" and make 'in' the variable holding
> the stream and automatically close it when we reach the end of the
> block.

This is not a better example, at least not for C++, because every C++ 
programmer would write it this way, with a local variable:

{ 
  ifstream in("filename");
  /* Do stuff with 'in' */
}

At the end of the block, or even at a return within the block, "in" is 
destroyed and the close method is called on it.

-- 
Frank Bu�, ··@frank-buss.de
http://www.frank-buss.de, http://www.it4-systems.de
From: Pascal Costanza
Subject: Re: macros
Date: 
Message-ID: <cfll9h$3mt$1@newsreader2.netcologne.de>
Frank Buss wrote:

> Peter Seibel <·····@javamonkey.com> wrote:
> 
>>But you could argue that this is really a lisp-1 vs lisp-2 problem. A
>>better example, I think, would be something like with_open_file. I
>>want to be able to write:
>>
>>  with_open_file(in, "filename") {
>>    /* Do stuff with 'in' */
>>  }
>>
>>and have it mean, open "filename" and make 'in' the variable holding
>>the stream and automatically close it when we reach the end of the
>>block.
> 
> This is not a better example, at least not for C++, because every C++ 
> programmer would write it this way, with a local variable:
> 
> { 
>   ifstream in("filename");
>   /* Do stuff with 'in' */
> }
> 
> At the end of the block, or even at a return within the block, "in" is 
> destroyed and the close method is called on it.

I don't think this is a valid counter example, because you are just 
reusing a feature that someone else has implemented for you. The 
question is how to create that feature in the first place. However, I 
think there are again some counter arguments to that position, so I 
don't want to go into too much detail here.

Instead, I propose another challenge. How do you implement the following 
in ····@!&^%?

aif int test_result = some_test() {
   ...
} else { ...
}

If the test succeeds (resulting in something other than 0), the first 
block is executed. In that block, the variable test_result (or whatever 
name the programmer wants) is visible and bound to the test result. 
Otherwise, the second block is executed, and that variable is not 
visible. Bonus points if you don't need to surround those blocks by 
curly braces, but instead can also use single statements. I don't care 
if you have to add parentheses or semi-colons at random places to make 
this work. ;)

(I don't say this is impossible or only possible in inelegant ways. I 
don't know about all the various preprocessing tools for C-based 
languages, so it's hard to make such a statement. I'm rather just curious.)

Another challenge has been posted by Guy Steele to the ll1 mailing list 
some time ago:

"The goal is to have something that looks like a function that takes a 
(numerical) function as an argument and finds its roots, or a root. 
Something like this:

  (findroots (lambda (a) (* (sin a) (+ a (* 3 a)))))"

See http://www.ai.mit.edu/~gregs/ll1-discuss-archive-html/msg02088.html 
for the full description.

He concludes with "By the way: to fans of Lisp macros, any macro 
facility incapable of this particular application is not the true macro 
facility."


Pascal

P.S.: Please always keep in mind that these questions are _not_ about 
whether something is possible at all. This is always the case due to 
Turing equivalence. The question is always: How convenient is it to make 
certain features work, and what drawbacks do you add to the rest of the 
language by adding some specific feature?

-- 
Tyler: "How's that working out for you?"
Jack: "Great."
Tyler: "Keep it up, then."
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87pt5t8r0f.fsf@marc0.dyndns.org>
Pascal Costanza on Sat, 14 Aug 2004 20:22:40 +0200 writes:

> Instead, I propose another challenge. How do you implement the
> following in ····@!&^%?
>
> aif int test_result = some_test() {
>    ...
> } else { ...
> }
>
> If the test succeeds (resulting in something other than 0), the first
> block is executed. In that block, the variable test_result (or
> whatever name the programmer wants) is visible and bound to the test
> result. Otherwise, the second block is executed, and that variable is
> not visible. Bonus points if you don't need to surround those blocks
> by curly braces, but instead can also use single statements. I don't
> care if you have to add parentheses or semi-colons at random places to
> make this work. ;)
>
> (I don't say this is impossible or only possible in inelegant ways. I
> don't know about all the various preprocessing tools for C-based
> languages, so it's hard to make such a statement. I'm rather just
> curious.)

#include <stdio.h>
#include <time.h>

#define aif(var, test, thenblock, elseblock) \
  { \
    int aif_tmp_cll_20040814_2103; \
    if ((aif_tmp_cll_20040814_2103 = test)) \
      { \
        var = aif_tmp_cll_20040814_2103; \
        thenblock; \
      } \
    else \
      { \
        elseblock; \
      } \
  }

int
main (int argc, char *argv[])
{
  /* the following expands to

  { int aif_tmp_cll_20040814_2103; if ((aif_tmp_cll_20040814_2103 = time (((void *)0)))) { int test_result = aif_tmp_cll_20040814_2103; printf ("%d #0\n", test_result); } else { { printf ("none #1.\n"); printf ("none #2.\n"); }; } };
  */

  aif (int test_result, time (NULL),
    printf ("%d #0\n", test_result),
  {
    printf ("none #1.\n");
    printf ("none #2.\n");
  });

  /* the following expands to

  { int aif_tmp_cll_20040814_2103; if ((aif_tmp_cll_20040814_2103 = 0 && 1)) { int test_result = aif_tmp_cll_20040814_2103; { printf ("%d\n #3\n", test_result); printf ("%d\n #5\n", test_result); }; } else { printf ("none #4.\n"); } };
  */

  aif (int test_result, 0 && 1,
       {
         printf ("%d\n #3\n", test_result);
         printf ("%d\n #5\n", test_result);
       },
       printf ("none #4.\n"));

  return 0;
}

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87isbl8pq2.fsf@marc0.dyndns.org>
Marco Parrone on Sat, 14 Aug 2004 19:25:23 GMT writes:

> #define aif(var, test, thenblock, elseblock) \
>   { \
>     int aif_tmp_cll_20040814_2103; \
>     if ((aif_tmp_cll_20040814_2103 = test)) \
>       { \
>         var = aif_tmp_cll_20040814_2103; \
>         thenblock; \
>       } \
>     else \
>       { \
>         elseblock; \
>       } \
>   }

the previous would make you lose precision with floats, and alike,
because the conversion to int.

#define aif(type, var, test, thenblock, elseblock) \
  { \
    type aif_tmp_cll_20040814_2103; \
    if ((aif_tmp_cll_20040814_2103 = test)) \
      { \
        type var = aif_tmp_cll_20040814_2103; \
        thenblock; \
      } \
    else \
      { \
        elseblock; \
      } \
  }

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Pascal Bourguignon
Subject: Re: macros
Date: 
Message-ID: <87n00xcwpi.fsf@thalassa.informatimago.com>
Marco Parrone <·····@autistici.org> writes:

> Pascal Costanza on Sat, 14 Aug 2004 20:22:40 +0200 writes:
> 
> > Instead, I propose another challenge. How do you implement the
> > following in ····@!&^%?
> >
> > aif int test_result = some_test() {
> >    ...
> > } else { ...
> > }

> #define aif(var, test, thenblock, elseblock) \
>   { \
>     int aif_tmp_cll_20040814_2103; \
>     if ((aif_tmp_cll_20040814_2103 = test)) \
>       { \
>         var = aif_tmp_cll_20040814_2103; \
>         thenblock; \
>       } \
>     else \
>       { \
>         elseblock; \
>       } \
>   }


Of course. But note that:

1- the cpp solution involves parenthesis like in Lisp. This is bad
   because it does not respect the C look-and-feel.

        aif(bool up,state>2,
            { do_some_work(up);
              go_to_sleep();
            },
            wake_up();)

    vs:  

        aif(bool up;state>2){
           do_some_work(up);
           go_to_sleep();
        }else{
           wake_up();
        }

2- the use of cpp macro introduce weird syntactic shifts. Instead of
   the normal ';' to separate clauses (like in for(;;)), you have to
   use ',', therefore you have to add parenthesis to use the C
   sequence operator ','.

3- cpp specifications and implementations have very short limits on
   the maximum size their arguments can be, the maximum size the
   generated text can be, and the characters that can be included as
   arguments (some implementations have great difficulties with
   NEW-LINES inside macro arguments).  The limits can be as low as 512
   characters!  That's why for the most useful macros, you actually
   need to introduce in-middle and at-end keywords/macros, like in
   NS_DURING / NS_HANDLER / NS_ENDHANDLER, and cpp must rely on the
   underlying C compiler to check the syntaxis.


This is all well known. Of course, some things can be done with cpp,
but it's rather like trying to build the Empire State Building
(natural size) with Lego(TM), while with Lisp Macros, it would be more
like using a star-trek xerox machine for buildings.

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Our enemies are innovative and resourceful, and so are we. They never
stop thinking about new ways to harm our country and our people, and
neither do we.
From: Pascal Costanza
Subject: Re: macros
Date: 
Message-ID: <cfm4i3$61l$1@newsreader2.netcologne.de>
Marco Parrone wrote:

> #include <stdio.h>
> #include <time.h>
> 
> #define aif(var, test, thenblock, elseblock) \
>   { \
>     int aif_tmp_cll_20040814_2103; \
>     if ((aif_tmp_cll_20040814_2103 = test)) \
>       { \
>         var = aif_tmp_cll_20040814_2103; \
>         thenblock; \
>       } \
>     else \
>       { \
>         elseblock; \
>       } \
>   }

This is neat. However, you are statically creating a temporary variable 
name, something you would do with uninterned symbols in Lisp, or would 
get for free with hygienic macro systems. This should bite you when you 
actually need to create a variable number of temporary variable names, 
depending on the actual input for the macro.


Pascal

-- 
Tyler: "How's that working out for you?"
Jack: "Great."
Tyler: "Keep it up, then."
From: Frank Buss
Subject: Re: macros
Date: 
Message-ID: <cflp50$ba2$1@newsreader2.netcologne.de>
Pascal Costanza <········@web.de> wrote:

> Instead, I propose another challenge. How do you implement the
> following in ····@!&^%?
> 
> aif int test_result = some_test() {
>    ...
> } else { ...
> }
> 
> If the test succeeds (resulting in something other than 0), the first 
> block is executed. In that block, the variable test_result (or
> whatever name the programmer wants) is visible and bound to the test
> result. Otherwise, the second block is executed, and that variable is
> not visible. Bonus points if you don't need to surround those blocks
> by curly braces, but instead can also use single statements. I don't
> care if you have to add parentheses or semi-colons at random places to
> make this work. ;)

I can't see any useful application for this, but it could be written
with the C-macro Marco wrote.

Of course, it doesn't look as nice as in Lisp:

(defmacro aif (var fun block1 block2)
  (let ((funvalue (funcall fun)))
    (if (/= 0 funvalue)
        `(let ((,var ,funvalue)) ,block1) block2)))

(defun result-0 () 0)
(defun result-2 () 2)

(let ((test-result 3))
  (aif test-result result-0
       (princ test-result)
       (princ test-result)))

(let ((test-result 3))
  (aif test-result result-2
       (princ test-result)
       (princ test-result)))

> Another challenge has been posted by Guy Steele to the ll1 mailing
> list some time ago:
> 
> "The goal is to have something that looks like a function that takes a
> (numerical) function as an argument and finds its roots, or a root. 
> Something like this:
> 
>   (findroots (lambda (a) (* (sin a) (+ a (* 3 a)))))"
> 
> See
> http://www.ai.mit.edu/~gregs/ll1-discuss-archive-html/msg02088.html 
> for the full description.
> 
> He concludes with "By the way: to fans of Lisp macros, any macro 
> facility incapable of this particular application is not the true
> macro facility."

yes, that's not possible with simple macros. But you can do such
compile-level-programming with C++ templates: 

http://spirit.sourceforge.net/distrib/spirit_1_7_0/libs/spirit/doc/style_guide.html 

if you really want to write code like this for implementing it :-)

http://cvs.sourceforge.net/viewcvs.py/spirit/spirit/boost/spirit/core/composite/impl/list.ipp?view=markup 

-- 
Frank Bu�, ··@frank-buss.de
http://www.frank-buss.de, http://www.it4-systems.de
From: Vassil Nikolov
Subject: Re: macros
Date: 
Message-ID: <lz8ychcwyx.fsf@janus.vassil.nikolov.names>
Frank Buss <··@frank-buss.de> writes:

> Pascal Costanza <········@web.de> wrote:
>
>> Instead, I propose another challenge. How do you implement the
>> following in ····@!&^%?
>> 
>> aif int test_result = some_test() {
>>    ...
>> } else { ...
>> }
>> 
>> If the test succeeds (resulting in something other than 0), the first 
>> block is executed. In that block, the variable test_result (or
>> whatever name the programmer wants) is visible and bound to the test
>> result. Otherwise, the second block is executed, and that variable is
>> not visible. Bonus points if you don't need to surround those blocks
>> by curly braces, but instead can also use single statements. I don't
>> care if you have to add parentheses or semi-colons at random places to
>> make this work. ;)
>
> I can't see any useful application for this, but it could be written
> with the C-macro Marco wrote.
>
> Of course, it doesn't look as nice as in Lisp:
>
> (defmacro aif (var fun block1 block2)
>   (let ((funvalue (funcall fun)))
>     (if (/= 0 funvalue)
>         `(let ((,var ,funvalue)) ,block1) block2)))


  But I wouldn't want fun to be called, and its value examined, at
  macroexpand time (besides, the second argument to the macro should
  be an expression, rather than a function, but that is somewhat less
  important).  In other words, I'd want (aif var fun block1 block2) to
  _expand_ into (something like)

    (let ((funvalue (funcall fun)))
      (if funvalue (let ((var funvalue)) block1)
        block2))

  or, to make this closer to a real implementation,
  (aif var test-expr expr-1 expr-2) to expand into

    (let ((#:test-result-00001 test-expr))
      (if #:test-result-00001
          (let ((var #:test-result-00001))
            expr-1)
        expr-2))

  with the obvious implementation of

    (defmacro aif (var test-expr expr-1 expr-2)
      (let ((aux (gensym "test-result-")))
        `(let ((,aux ,test-expr))
           (if ,aux
               (let ((,var ,aux)) ,expr-1)
             ,expr-2))))

  Of course, the point of this exercise is to do it in C/C++,
  not in Lisp where it is not a problem at all.

  ---Vassil.

-- 
Vassil Nikolov <········@poboxes.com>

Hollerith's Law of Docstrings: Everything can be summarized in 72 bytes.
From: Pascal Costanza
Subject: Re: macros
Date: 
Message-ID: <cfm4tl$6ea$1@newsreader2.netcologne.de>
Frank Buss wrote:

> Pascal Costanza <········@web.de> wrote:
> 
>>Instead, I propose another challenge. How do you implement the
>>following in ····@!&^%?
>>
>>aif int test_result = some_test() {
>>   ...
>>} else { ...
>>}
>>
>>If the test succeeds (resulting in something other than 0), the first 
>>block is executed. In that block, the variable test_result (or
>>whatever name the programmer wants) is visible and bound to the test
>>result. Otherwise, the second block is executed, and that variable is
>>not visible. Bonus points if you don't need to surround those blocks
>>by curly braces, but instead can also use single statements. I don't
>>care if you have to add parentheses or semi-colons at random places to
>>make this work. ;)
> 
> I can't see any useful application for this, but it could be written
> with the C-macro Marco wrote.
> 
> Of course, it doesn't look as nice as in Lisp:
> 
> (defmacro aif (var fun block1 block2)
>   (let ((funvalue (funcall fun)))
>     (if (/= 0 funvalue)
>         `(let ((,var ,funvalue)) ,block1) block2)))

What I actually had in mind is this:

(defmacro aif ((var form) then else)
   (let ((test (gensym)))
     `(let ((,test ,form))
        (if ,test
           (let ((,var ,test))
             ,then)
           ,else))))

The requirement to check for 0 was only there because 0 is the false 
value in C.


Pascal

-- 
Tyler: "How's that working out for you?"
Jack: "Great."
Tyler: "Keep it up, then."
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: macros
Date: 
Message-ID: <pan.2004.08.14.22.01.52.894702@knm.org.pl>
On Sat, 14 Aug 2004 20:22:40 +0200, Pascal Costanza wrote:

> Instead, I propose another challenge. How do you implement the following 
> in ····@!&^%?
> 
> aif int test_result = some_test() {
>    ...
> } else { ...
> }
> 
> If the test succeeds (resulting in something other than 0), the first 
> block is executed. In that block, the variable test_result (or whatever 
> name the programmer wants) is visible and bound to the test result. 
> Otherwise, the second block is executed, and that variable is not 
> visible.

If you don't insist on making the variable invisible in the else part,
it already exists in C++:

   if (int test_result = some_test()) {
      ...
   }
   else {
      ...
   }

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Pascal Costanza
Subject: Re: macros
Date: 
Message-ID: <cfm4um$6ea$2@newsreader2.netcologne.de>
Marcin 'Qrczak' Kowalczyk wrote:

> If you don't insist on making the variable invisible in the else part,
> it already exists in C++:

...but of course, I do insist. ;)


Pascal

-- 
Tyler: "How's that working out for you?"
Jack: "Great."
Tyler: "Keep it up, then."
From: Marco Parrone
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87fz6paeqb.fsf@marc0.dyndns.org>
[Hi Peter, I'm sorry for having replied by mail by mistake.]

Peter Seibel on Sat, 14 Aug 2004 15:29:05 GMT writes:

> yours is still only a half solution since you are limited to textual
> substitution:

Agreed, that's just textual substitution.

I don't claim that CL/Scheme macros are not more usable, or more
suitable for complex things, I just want to verify that the same can
not be done with C macros.

>   #include <stdio.h>
>
>   #define repeat do {
>   #define until } while
>
>   int
>   main (int argc, char *argv[])
>   {
>     int repeat = 10;
>
>     repeat
>       printf ("%d ", repeat);
>       --repeat;
>     until (repeat != 0);
>
>     printf ("\n");
>     return 0;
>   }

> But you could argue that this is really a lisp-1 vs lisp-2 problem. A

Yes, even

...
  int for;
...

or

...
  char while;
...

are errors in C.

> better example, I think, would be something like with_open_file. I
> want to be able to write:
>
>   with_open_file(in, "filename") {
>     /* Do stuff with 'in' */
>   }
>
> and have it mean, open "filename" and make 'in' the variable holding
> the stream and automatically close it when we reach the end of the
> block.

#include <stdio.h>

#define with_open_file(name, filename, opentype, body) \
  { FILE *name = fopen (filename, opentype); body; fclose (name); }

int
main (int argc, char *argv[])
{
  /* the following expands to

  { FILE *in = fopen ("test.txt", "r"); { char c = fgetc (in); while (c != (-1)) { putchar (c); c = fgetc (in); } }; fclose (in); };

  */
  with_open_file (in, "test.txt", "r",
  {
    char c = fgetc (in);
    while (c != EOF)
      {
	putchar (c);
	c = fgetc (in);
      }
  });
  return 0;
}
From: Peter Seibel
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <m38ych4du2.fsf@javamonkey.com>
Marco Parrone <·····@autistici.org> writes:

> [Hi Peter, I'm sorry for having replied by mail by mistake.]
>
> Peter Seibel on Sat, 14 Aug 2004 15:29:05 GMT writes:
>
>> yours is still only a half solution since you are limited to textual
>> substitution:
>
> Agreed, that's just textual substitution.
>
> I don't claim that CL/Scheme macros are not more usable, or more
> suitable for complex things, I just want to verify that the same can
> not be done with C macros.

Well, not all things that can be done with Lisp macros can be done
with textual substitution. The with_open_file example wasn't, in
retrospect, really the best. (Though seem my comments below.) The real
trick of Lisp macros is that you get a chance to manipulate the code
passed to the macro as data, not just interpolate it as text.

Here's a silly example but one that don't think has an analog in CPP:

  (defun find-function-calls (sexp)
    (when (and (listp sexp) (symbolp (first sexp)) (fboundp (first sexp)))
      (delete-duplicates (cons (first sexp) (mapcan #'find-function-calls (rest sexp))))))

  (defmacro list-functions-called (&body body)
    `(progn
       (format t "Functions called: ~a~%" ',(mapcan #'find-function-calls body))
       ,@body))

>> better example, I think, would be something like with_open_file. I
>> want to be able to write:
>>
>>   with_open_file(in, "filename") {
>>     /* Do stuff with 'in' */
>>   }
>>
>> and have it mean, open "filename" and make 'in' the variable holding
>> the stream and automatically close it when we reach the end of the
>> block.
>
> #include <stdio.h>
>
> #define with_open_file(name, filename, opentype, body) \
>   { FILE *name = fopen (filename, opentype); body; fclose (name); }
>
> int
> main (int argc, char *argv[])
> {
>   /* the following expands to
>
>   { FILE *in = fopen ("test.txt", "r"); { char c = fgetc (in); while (c != (-1)) { putchar (c); c = fgetc (in); } }; fclose (in); };
>
>   */
>   with_open_file (in, "test.txt", "r",
>   {
>     char c = fgetc (in);
>     while (c != EOF)
>       {
> 	putchar (c);
> 	c = fgetc (in);
>       }
>   });
>   return 0;
> }

Okay, but you didn't quite meet my requirements--I don't want to write
that, I want to write exactly what I wrote before. To make it
concrete, your example code should look like this:

   with_open_file (in, "test.txt") 
   {
     char c = fgetc (in);
     while (c != EOF)
       {
 	putchar (c);
 	c = fgetc (in);
       }
   }

Notice where all the parens, braces, and semicolons go. This may seem
nitpicky but the point of (Lisp) macros is to allow us to write
exactly what we want and let the computer take care of translatining
it into something that will compile. That you had to change the rules
slightly to turn the example I proposed into something that could be
expressed as text substitution shows the relative expressiveness of
CPP vs Lisp macros. In this case it doesn't make a huge difference but
it does show that the CPP way is already running out of steam.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: mikel
Subject: Re: macros
Date: 
Message-ID: <XdCTc.4542$km7.2239@newssvr27.news.prodigy.com>
Peter Seibel wrote:

> Marco Parrone <·····@autistici.org> writes:
> 
> 
>>[Hi Peter, I'm sorry for having replied by mail by mistake.]
>>
>>Peter Seibel on Sat, 14 Aug 2004 15:29:05 GMT writes:
>>
>>
>>>yours is still only a half solution since you are limited to textual
>>>substitution:
>>
>>Agreed, that's just textual substitution.
>>
>>I don't claim that CL/Scheme macros are not more usable, or more
>>suitable for complex things, I just want to verify that the same can
>>not be done with C macros.
> 
> 
> Well, not all things that can be done with Lisp macros can be done
> with textual substitution. The with_open_file example wasn't, in
> retrospect, really the best.

Keep in mind what is was for: to illustrate that in the context of 
Lisp-style macros, constructs like it are a dime a dozen in the Lisp 
world (with-open-file, with-condition-restarts, with-hashtable-iterator, 
with-output-to-string, with-cstrs, with-session, with-editor-output, 
with-augmented-environment, with-resource, with-standard-io-syntax, 
with-recursive-lock, with-lock-grabbed, with-open-socket, 
with-fixed-allocation, with-compilation-unit, with-spinlock, 
with-coerced-pointer, with-dynamic-foreign-objects, 
with-transformed-rect...), but you scarcely ever see things like them 
outside it.

They're extremely useful, because they enable you to wrap a potentially 
messy or hazardous set of operations in a textually simple protective 
guard whose scope is lexically apparent. So why don't we see them in 
more places? Presumably because they are in general hard to do right.

So if they are hard to do right, why do we see so many of them in Lisp? 
Presumably because in Lisp they are not so hard to do right.

Where else do you see unwind-protect?

I ran into this problem a lot of times working on large projects using 
Lisp--the problem of explaining why Lisp was a good choice for 
implementing what I was doing. We would be asked what it gave us, and 
would give an answer, and the questioners would say "but I could do that 
with <insert language here>."

Well, that's not the point; you can do anything in any turing-complete 
language. The point is that, to take one example, five of use replicated 
40% of the features implemented by 60 people in a competing project in 
the same time. At the time we said we could do it because we did it in 
Lisp, but the management team concluded we could do it because we were 
unusually smart and hardworking. Now, I wouldn't want to contradict such 
obviously perceptive management, but the other folks were pretty darn 
smart and hardworking too. I must sheepishly admit that our real 
advantage was Lisp.

The fruit of my experience tells me that there is no percentage in 
answering the question "what can you do in Lisp that you can't do in 
<insert language here>?" Instead, it might be more fruitful to provide 
examples of idioms that are common in Lisp and uncommon elsewhere and 
discuss why that might be.

You can also profitably discuss idioms that are common elsewhere but 
uncommon in Lisp. A friend of mine wrote a well-regarded set of books 
called _The Modula-2 Software Component Library_ and we discussed my 
doing a Common Lisp version of it. It didn't go anywhere because upon 
examination we concluded that everything in it was either built into 
Common Lisp already, or scarecly more than trivial to implement. 
Similarly, certain very popular patterns nowadays (I'm thinking in 
particular of the visitor pattern) seem to be almost redundant in 
Lisp--they solve problems that scarcely exist if your implementation 
language is Lisp.

I didn't mean with-open-file to illustrate something you can't do with 
the C preprocessor, but to illustrate one of several families of idioms 
that are common in Lisp and uncommon elsewhere. It's also uncommon in 
other langauges (except, arguably, in Smalltalk and Forth) to build new 
languages into the language, but it's the commonest thing in the world 
in Lisp. Indeed, many whole languages were initially built as subsystems 
embedded in Lisp runtimes. Some of these have grown up to have quite 
successful indepdendent lives (Prolog, Smalltalk, ML...).

I think a really interested person could learn a lot of what makes Lisp 
special just by looking at how many and what kinds of things are 
idiomatic in Lisp projects that aren't done much in other languages, and 
what kinds of things are idiomatic in other languages but that no one 
seems to bother much with in Lisp.
From: Marco Gidde
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <lzn00x7ai7.fsf@tristan.br-automation.de>
Marco Parrone <·····@autistici.org> writes:

> >
> >   with_open_file(in, "filename") {
> >     /* Do stuff with 'in' */
> >   }
> >
> > and have it mean, open "filename" and make 'in' the variable holding
> > the stream and automatically close it when we reach the end of the
> > block.
> 
> #include <stdio.h>
> 
> #define with_open_file(name, filename, opentype, body) \
>   { FILE *name = fopen (filename, opentype); body; fclose (name); }
> 
> int
> main (int argc, char *argv[])
> {
>   /* the following expands to
> 
>   { FILE *in = fopen ("test.txt", "r"); { char c = fgetc (in); while (c != (-1)) { putchar (c); c = fgetc (in); } }; fclose (in); };
> 
>   */
>   with_open_file (in, "test.txt", "r",
>   {
>     char c = fgetc (in);
>     while (c != EOF)
>       {
> 	putchar (c);
> 	c = fgetc (in);
>       }
>   });
>   return 0;
> }

Of course some special handling for explicit returns within body is
missing, not to mention setjmp/longjmp. The cpp isn't made for things
like this, it's not even possible to give a correct definition of min
and/or max without the use of extensions.


-- 
Marco Gidde
From: Marco Antoniotti
Subject: Re: macros
Date: 
Message-ID: <cR3Uc.33$D5.10472@typhoon.nyu.edu>
Marco Parrone wrote:
> [Hi Peter, I'm sorry for having replied by mail by mistake.]
> 
> Peter Seibel on Sat, 14 Aug 2004 15:29:05 GMT writes:
> 
> 
>>yours is still only a half solution since you are limited to textual
>>substitution:
> 
> 
> Agreed, that's just textual substitution.
> 
> I don't claim that CL/Scheme macros are not more usable, or more
> suitable for complex things, I just want to verify that the same can
> not be done with C macros.
> 
> 
>>  #include <stdio.h>
>>
>>  #define repeat do {
>>  #define until } while
>>
>>  int
>>  main (int argc, char *argv[])
>>  {
>>    int repeat = 10;
>>
>>    repeat
>>      printf ("%d ", repeat);
>>      --repeat;
>>    until (repeat != 0);
>>
>>    printf ("\n");
>>    return 0;
>>  }
> 
> 
>>But you could argue that this is really a lisp-1 vs lisp-2 problem. A
> 
> 
> Yes, even
> 
> ...
>   int for;
> ...
> 
> or
> 
> ...
>   char while;
> ...
> 
> are errors in C.
> 
> 
>>better example, I think, would be something like with_open_file. I
>>want to be able to write:
>>
>>  with_open_file(in, "filename") {
>>    /* Do stuff with 'in' */
>>  }
>>
>>and have it mean, open "filename" and make 'in' the variable holding
>>the stream and automatically close it when we reach the end of the
>>block.
> 
> 
> #include <stdio.h>
> 
> #define with_open_file(name, filename, opentype, body) \
>   { FILE *name = fopen (filename, opentype); body; fclose (name); }
> 
> int
> main (int argc, char *argv[])
> {
>   /* the following expands to
> 
>   { FILE *in = fopen ("test.txt", "r"); { char c = fgetc (in); while (c != (-1)) { putchar (c); c = fgetc (in); } }; fclose (in); };
> 
>   */
>   with_open_file (in, "test.txt", "r",
>   {
>     char c = fgetc (in);
>     while (c != EOF)
>       {
> 	putchar (c);
> 	c = fgetc (in);
>       }
>   });
>   return 0;
> }

BZZZT!

This is not TRT.  You have to achieve the following


    with_open_file (in, "test.txt", "r")
    {
      char c = fgetc (in);
      while (c != EOF)
        {
  	putchar (c);
  	c = fgetc (in);
        }
    }

This you cannot do with the C preprocessor.

The best you can hope to achieve is


    with_open_file (in, "test.txt", "r")
    {
      char c = fgetc (in);
      while (c != EOF)
        {
  	putchar (c);
  	c = fgetc (in);
        }
    }
    elif_nepo_htiw;



Cheers
--
Marco
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87n00v85yh.fsf@marc0.dyndns.org>
Marco Antoniotti on Mon, 16 Aug 2004 10:50:48 -0400 writes:

> BZZZT!
>
> This is not TRT.  You have to achieve the following
>
>
>     with_open_file (in, "test.txt", "r")
>     {
>       char c = fgetc (in);
>       while (c != EOF)
>         {
>   	putchar (c);
>   	c = fgetc (in);
>         }
>     }
>
> This you cannot do with the C preprocessor.

With C99 yes :)

#include <stdio.h>

#define with_open_file(name, filename, opentype) for (FILE *cll = (FILE *) 1, *name = fopen (filename, opentype); cll; cll = (FILE *) 0, fclose (name))

int
main (int argc, char *argv[])
{

  with_open_file (in, "test.txt", "r")
  {
    char c = fgetc (in);
    while (c != EOF)
      {
	putchar (c);
	c = fgetc (in);
      }
  }
  return 0;
}

·····@marc0:~/tmp$ echo "test test test" > test.txt
·····@marc0:~/tmp$ gcc -std=c99 with_open_file.c
·····@marc0:~/tmp$ ./a.out
test test test
·····@marc0:~/tmp$ 

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Abdulaziz Ghuloum
Subject: Re: macros
Date: 
Message-ID: <cfrk14$3l8$1@hood.uits.indiana.edu>
Marco Parrone wrote:

> [...]
> #include <stdio.h>
> 
> #define with_open_file(name, filename, opentype) \
>   for (FILE *cll = (FILE *) 1, *name = fopen (filename, opentype); \
>        cll; \
>        cll = (FILE *) 0, fclose (name))
> [...]

What's `cll' for?  (other than shadowing my own cll by mistake)
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87fz6mnsbp.fsf@marc0.dyndns.org>
Abdulaziz Ghuloum on Mon, 16 Aug 2004 19:37:56 -0500 writes:

> Marco Parrone wrote:
>
>> [...]
>> #include <stdio.h>
>> #define with_open_file(name, filename, opentype) \
>>   for (FILE *cll = (FILE *) 1, *name = fopen (filename, opentype); \
>>        cll; \
>>        cll = (FILE *) 0, fclose (name))
>> [...]
>
> What's `cll' for?  (other than shadowing my own cll by mistake)

I missed to obfuscate the name after finishing testing the macro.

I liked the way Stefan Ram has done it with
`comp_lang_lisp_2004_08_14_18_10_40_02_00__'.

That's just a workaround to un-hygienic macros, but it seems to work.

However AFAIK `defmacro' is un-hygienic too, so that's not a point
against C macros IMHO.

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Edi Weitz
Subject: Re: macros
Date: 
Message-ID: <87acwu6wtq.fsf@bird.agharta.de>
On Tue, 17 Aug 2004 07:24:43 GMT, Marco Parrone <·····@autistici.org> wrote:

> That's just a workaround to un-hygienic macros, but it seems to
> work.
>
> However AFAIK `defmacro' is un-hygienic too, so that's not a point
> against C macros IMHO.

C macros don't have GENSYM available, though.

Edi.

-- 

"Lisp doesn't look any deader than usual to me."
(David Thornley, reply to a question older than most languages)

Real email: (replace (subseq ·········@agharta.de" 5) "edi")
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87k6vym5ss.fsf@marc0.dyndns.org>
Edi Weitz on Tue, 17 Aug 2004 09:35:45 +0200 writes:

> On Tue, 17 Aug 2004 07:24:43 GMT, Marco Parrone <·····@autistici.org> wrote:
>
>> That's just a workaround to un-hygienic macros, but it seems to
>> work.
>>
>> However AFAIK `defmacro' is un-hygienic too, so that's not a point
>> against C macros IMHO.
>
> C macros don't have GENSYM available, though.

Right.

However, (GNU) CPP gives you a counter (__LINE__) and token
concatenation (##), so you can roll your own version.

However I'm not really sure if the following does the equivalent thing.

#define gensym(prefix, line) gensym_helper  (prefix, line)
#define gensym_helper(prefix, line) prefix ## line

#define with_open_file(name, filename, opentype) \
  with_open_file_helper (name, filename, opentype, \
                          gensym(with_open_file, __LINE__))

#define with_open_file_helper(name, filename, opentype, cll) \
  for (FILE *name = fopen (filename, opentype), \
	 *cll = (void *) 1; \
       cll; \
       fclose (name), cll = NULL)

...

/*

the following expands to

  for (FILE *in = fopen ("test.txt", "r"), *with_open_file23 = (void *) 1; with_open_file23; fclose (in), with_open_file23 = ((void *)0))
  {
    char c = fgetc (in);
    while (c != (-1))
      {
 putchar (c);
 c = fgetc (in);
      }
  }

*/

  with_open_file (in, "test.txt", "r")
  {
    char c = fgetc (in);
    while (c != EOF)
      {
	putchar (c);
	c = fgetc (in);
      }
  }

...

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Frank Buss
Subject: Re: macros
Date: 
Message-ID: <cfsn76$os3$1@newsreader2.netcologne.de>
Marco Parrone <·····@autistici.org> wrote:

> However, (GNU) CPP gives you a counter (__LINE__) and token
> concatenation (##), so you can roll your own version.

this is better than using hardcoded names, but it is not the same as the 
Lisp-gensym, because you can always do "#define SOME_PREFIX_123" and a 
gensym at line 123 would produce the same name.

-- 
Frank Bu�, ··@frank-buss.de
http://www.frank-buss.de, http://www.it4-systems.de
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <873c2mm04w.fsf@marc0.dyndns.org>
Stefan Ram on 17 Aug 2004 11:43:09 GMT writes:

> Frank Buss <··@frank-buss.de> writes:
>>this is better than using hardcoded names, but it is not the
>>same as the Lisp-gensym, because you can always do "#define
>>SOME_PREFIX_123" and a gensym at line 123 would produce the
>>same name.
>
>   I can not solve this problem, because AFAIK C does not have a
>   special namespace reserved for such uses.

#define gensym(prefix, line) gensym_helper  (prefix, line)
#define gensym_helper(prefix, line) gensym_reserved_namespace_ ## prefix ## line

  ;)

>   The macro-gensym with __LINE__ has another problem: Someone
>   might call the macro multiple times on the same line of source
>   code. 

Right.

IMHO this is coherent with CPP (where newlines matter), but not with C.

A workaround to the workaround would be renaming it:

#define gensym_only_one_per_line(prefix, line) gensym_only_one_per_line_helper  (prefix, line)

#define gensym_only_one_per_line_helper(prefix, line) gensym_reserved_namespace_ ## prefix ## line

 :))

>   This problem is addressed by the following remark:
>
>   If we allow the Lisp-programmers to use their Lisp-interpreter
>   to build lists (which then might be evaluated), why not allow
>   the C-programmers the same usage of their C compiler?
>
>   The following program was generated by a C program.

(working code snipped)

>   I believe, a C program that generates a C program to be
>   somewhat similar to a Lisp macro.

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Frank Buss
Subject: Re: macros
Date: 
Message-ID: <cfsv0j$98f$1@newsreader2.netcologne.de>
···@zedat.fu-berlin.de (Stefan Ram) wrote:

>   If we allow the Lisp-programmers to use their Lisp-interpreter
>   to build lists (which then might be evaluated), why not allow
>   the C-programmers the same usage of their C compiler?

yes, this is possible, but you can't compare it to Lisp, where the DEFMACRO 
is part of the language without a pre-compiler. At the end you'll prove 
only Greenspun's Tenth Rule of Programming :-)

"Any sufficiently complicated C or Fortran program contains an ad-hoc, 
informally-specified bug-ridden slow implementation of half of Common 
Lisp." 

-- 
Frank Bu�, ··@frank-buss.de
http://www.frank-buss.de, http://www.it4-systems.de
From: Pascal Bourguignon
Subject: Re: macros
Date: 
Message-ID: <878ycd99v4.fsf@thalassa.informatimago.com>
Frank Buss <··@frank-buss.de> writes:

> ···@zedat.fu-berlin.de (Stefan Ram) wrote:
> 
> >   If we allow the Lisp-programmers to use their Lisp-interpreter
> >   to build lists (which then might be evaluated), why not allow
> >   the C-programmers the same usage of their C compiler?
> 
> yes, this is possible, but you can't compare it to Lisp, where the DEFMACRO 
> is part of the language without a pre-compiler. At the end you'll prove 
> only Greenspun's Tenth Rule of Programming :-)

Yes, this is possible, AND you MUST compare it to Lisp. IMO that's
even the only correct way to compare C and Lisp with respect to
defmacro feature.

The brightest C programmers have always used DEFMACRO without knowing
it: they've written generating programs: lex, yacc, and other special
purpose "macro" programs such as make or comment5[1].


We should be comparing these C programs with Lisp macros: complexity,
size, performance, ease of use, etc.

 
> "Any sufficiently complicated C or Fortran program contains an ad-hoc, 
> informally-specified bug-ridden slow implementation of half of Common 
> Lisp." 

Obviously.




[1] comment5 is a pre-processor specific to the sources of
    clisp. Check it, it's nothing more than a big defmacro written in
    C to process C sources.

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Our enemies are innovative and resourceful, and so are we. They never
stop thinking about new ways to harm our country and our people, and
neither do we.
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87pt5qm7l4.fsf@marc0.dyndns.org>
Abdulaziz Ghuloum on Mon, 16 Aug 2004 19:37:56 -0500 writes:

> Marco Parrone wrote:
>
>> [...]
>> #include <stdio.h>
>> #define with_open_file(name, filename, opentype) \
>>   for (FILE *cll = (FILE *) 1, *name = fopen (filename, opentype); \
>>        cll; \
>>        cll = (FILE *) 0, fclose (name))
>> [...]
>
> What's `cll' for?  (other than shadowing my own cll by mistake)


If you meant that it's not needed, you are right too.

#define with_open_file(name, filename, opentype) \
  for (FILE *name = fopen (filename, opentype); \
       name; \
       fclose (name), name = NULL)

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Marco Antoniotti
Subject: Re: macros
Date: 
Message-ID: <5LbUc.35$D5.11533@typhoon.nyu.edu>
Marco Parrone wrote:
> Marco Antoniotti on Mon, 16 Aug 2004 10:50:48 -0400 writes:
> 
> 
>>BZZZT!
>>
>>This is not TRT.  You have to achieve the following
>>
>>
>>    with_open_file (in, "test.txt", "r")
>>    {
>>      char c = fgetc (in);
>>      while (c != EOF)
>>        {
>>  	putchar (c);
>>  	c = fgetc (in);
>>        }
>>    }
>>
>>This you cannot do with the C preprocessor.
> 
> 
> With C99 yes :)
> 
> #include <stdio.h>
> 
> #define with_open_file(name, filename, opentype) for (FILE *cll = (FILE *) 1, *name = fopen (filename, opentype); cll; cll = (FILE *) 0, fclose (name))
> 
> int
> main (int argc, char *argv[])
> {
> 
>   with_open_file (in, "test.txt", "r")
>   {
>     char c = fgetc (in);
>     while (c != EOF)
>       {
> 	putchar (c);
> 	c = fgetc (in);
>       }
>   }
>   return 0;
> }
> 
> ·····@marc0:~/tmp$ echo "test test test" > test.txt
> ·····@marc0:~/tmp$ gcc -std=c99 with_open_file.c
> ·····@marc0:~/tmp$ ./a.out
> test test test
> ·····@marc0:~/tmp$ 
> 

Very cute.  Now stick a longjmp/setjmp in the increment portion of the 
for loop and make sure that the file is closed if you get a runtime 
error in the body :)

Cheers

--
Marco
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87u0v0be74.fsf@marc0.dyndns.org>
Marco Antoniotti on Mon, 16 Aug 2004 19:50:25 -0400 writes:

> Very cute.  Now stick a longjmp/setjmp in the increment portion of the
> for loop and make sure that the file is closed if you get a runtime
> error in the body :)

:)

/* with-open-file-semi-safe.c starts here */

#include <malloc.h>
#include <stdio.h>
#include <setjmp.h>
#include <signal.h>

#define gensym_eq_prefix_on_neq_lines(prefix, line) \
  gensym_eq_prefix_on_neq_lines_helper(prefix, line)

#define gensym_eq_prefix_on_neq_lines_helper(prefix, line) \
  gensym_reserved_namespace_ ## prefix ## line

#define with_open_file(name, filename, opentype) \
  with_open_file_helper \
   (name, filename, opentype, \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_cleanup_code_label, __LINE__), \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_prev_cleanup_code, __LINE__), \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_prev_sighandl, __LINE__), \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_bogus1, __LINE__), \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_bogus2, __LINE__))

/* WARNING!: not thread safe. */
/* FIXME!: handle more signals. */
#define with_open_file_helper(name, filename, opentype, cleanup_code_label, prev_cleanup_code, prev_sighandl, bogus1, bogus2) \
  for (void *prev_cleanup_code = unwind_protect_cleanup_code, \
	 *prev_sighandl = signal (SIGSEGV, NULL), \
         *bogus1 = unwind_protect_cleanup_code = malloc (sizeof (jmp_buf)), \
         *bogus2 = signal (SIGSEGV, &unwind_protect_helper_sighandler), \
	 *name = fopen (filename, opentype); \
       name;  \
       fclose ((FILE *) name), \
	 printf ("ok\n"),  \
	 signal (SIGSEGV, prev_sighandl), \
	 free (unwind_protect_cleanup_code), \
	 unwind_protect_cleanup_code = (prev_cleanup_code) \
                                         ? prev_cleanup_code : NULL, \
	 name = NULL) \
    if (! setjmp (*unwind_protect_cleanup_code))

jmp_buf *unwind_protect_cleanup_code = NULL;

void unwind_protect_helper_sighandler (int sig)
{
  signal (sig, unwind_protect_helper_sighandler);
  longjmp (*unwind_protect_cleanup_code, 1);
}

/* test2.txt content: "test.txt\n" */
/* test.txt content: "test test test\n" */
int main (int argc, char *argv [])
{
  with_open_file (in, "test2.txt", "r")
  {
    char *nextfilename = NULL;
    size_t nextfilename_size = 0;
    char **p = NULL;
    nextfilename_size = getline (&nextfilename, &nextfilename_size, in);
    nextfilename [--nextfilename_size] = 0;
    printf ("[cat %s: [", nextfilename);
    with_open_file (in, nextfilename, "r")
    {
      char **p = NULL;
      char c = fgetc (in);
      int life = 3;
      while (c != EOF)
	{
	  putchar (c);
	  c = fgetc (in);
	  if (! (--life))
	    *p = "segfault!";
	}
      printf ("]]\n");
    }
    raise (SIGSEGV);
    *p = "segfault!";
  }
  return 0;
}

/* with-open-file-semi-safe.c ends here. */

·····@marc0:~/tmp$ gcc -Wall -Wno-unused -D_GNU_SOURCE -std=c99 with-open-file-semi-safe.c
·····@marc0:~/tmp$ # `-D_GNU_SOURCE' is for `getline' ...
·····@marc0:~/tmp$ ./a.out
[cat test.txt: [tesok
ok
·····@marc0:~/tmp$ 

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87pt5obdn2.fsf@marc0.dyndns.org>
Marco Parrone on Wed, 18 Aug 2004 16:35:14 GMT writes:

(snip)
> #define with_open_file_helper(name, filename, opentype, cleanup_code_label, prev_cleanup_code, prev_sighandl, bogus1, bogus2) \
>   for (void *prev_cleanup_code = unwind_protect_cleanup_code, \
                                   ^^^^^^
> 	 *prev_sighandl = signal (SIGSEGV, NULL), \
>          *bogus1 = unwind_protect_cleanup_code = malloc (sizeof (jmp_buf)), \
                     ^^^^^^
>          *bogus2 = signal (SIGSEGV, &unwind_protect_helper_sighandler), \
                                       ^^^^^
> 	 *name = fopen (filename, opentype); \
(snip)

the `unwind_protect_something' are here because this macro (and its
"gensymmer") was a recomposition of:

#define unwind_protect(protected_form, cleanup_form) \
  unwind_protect_helper \
   (protected_form, \
    cleanup_form, \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_cleanup_code_label, __LINE__), \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_prev_cleanup_code, __LINE__), \
    gensym_eq_prefix_on_neq_lines \
     (unwind_protect_prev_sighandl, __LINE__))

/* WARNING!: not thread safe. */
/* FIXME!: handle more signals. */
#define unwind_protect_helper(protected_form, cleanup_form, cleanup_code_label, prev_cleanup_code, prev_sighandl) \
  { \
    __label__ cleanup_code_label; \
    jmp_buf *prev_cleanup_code = unwind_protect_cleanup_code; \
    void *prev_sighandl = signal (SIGSEGV, NULL); \
    unwind_protect_cleanup_code = malloc (sizeof (jmp_buf)); \
    signal (SIGSEGV, &unwind_protect_helper_sighandler); \
    if (setjmp (*unwind_protect_cleanup_code)) \
      goto cleanup_code_label; \
    protected_form; \
  cleanup_code_label: \
    cleanup_form; \
    signal (SIGSEGV, prev_sighandl); \
    free (unwind_protect_cleanup_code); \
    unwind_protect_cleanup_code = (prev_cleanup_code) \
                                  ? prev_cleanup_code \
                                  : NULL; \
  }


-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Marco Antoniotti
Subject: Re: macros
Date: 
Message-ID: <Bd3Vc.40$D5.13176@typhoon.nyu.edu>
I am impressed :)  What do you do if the file already exists? :)  What 
if it does not exist? :)

Cheers
--
Marco





Marco Parrone wrote:
> Marco Antoniotti on Mon, 16 Aug 2004 19:50:25 -0400 writes:
> 
> 
>>Very cute.  Now stick a longjmp/setjmp in the increment portion of the
>>for loop and make sure that the file is closed if you get a runtime
>>error in the body :)
> 
> 
> :)
> 
> /* with-open-file-semi-safe.c starts here */
> 
> #include <malloc.h>
> #include <stdio.h>
> #include <setjmp.h>
> #include <signal.h>
> 
> #define gensym_eq_prefix_on_neq_lines(prefix, line) \
>   gensym_eq_prefix_on_neq_lines_helper(prefix, line)
> 
> #define gensym_eq_prefix_on_neq_lines_helper(prefix, line) \
>   gensym_reserved_namespace_ ## prefix ## line
> 
> #define with_open_file(name, filename, opentype) \
>   with_open_file_helper \
>    (name, filename, opentype, \
>     gensym_eq_prefix_on_neq_lines \
>      (unwind_protect_cleanup_code_label, __LINE__), \
>     gensym_eq_prefix_on_neq_lines \
>      (unwind_protect_prev_cleanup_code, __LINE__), \
>     gensym_eq_prefix_on_neq_lines \
>      (unwind_protect_prev_sighandl, __LINE__), \
>     gensym_eq_prefix_on_neq_lines \
>      (unwind_protect_bogus1, __LINE__), \
>     gensym_eq_prefix_on_neq_lines \
>      (unwind_protect_bogus2, __LINE__))
> 
> /* WARNING!: not thread safe. */
> /* FIXME!: handle more signals. */
> #define with_open_file_helper(name, filename, opentype, cleanup_code_label, prev_cleanup_code, prev_sighandl, bogus1, bogus2) \
>   for (void *prev_cleanup_code = unwind_protect_cleanup_code, \
> 	 *prev_sighandl = signal (SIGSEGV, NULL), \
>          *bogus1 = unwind_protect_cleanup_code = malloc (sizeof (jmp_buf)), \
>          *bogus2 = signal (SIGSEGV, &unwind_protect_helper_sighandler), \
> 	 *name = fopen (filename, opentype); \
>        name;  \
>        fclose ((FILE *) name), \
> 	 printf ("ok\n"),  \
> 	 signal (SIGSEGV, prev_sighandl), \
> 	 free (unwind_protect_cleanup_code), \
> 	 unwind_protect_cleanup_code = (prev_cleanup_code) \
>                                          ? prev_cleanup_code : NULL, \
> 	 name = NULL) \
>     if (! setjmp (*unwind_protect_cleanup_code))
> 
> jmp_buf *unwind_protect_cleanup_code = NULL;
> 
> void unwind_protect_helper_sighandler (int sig)
> {
>   signal (sig, unwind_protect_helper_sighandler);
>   longjmp (*unwind_protect_cleanup_code, 1);
> }
> 
> /* test2.txt content: "test.txt\n" */
> /* test.txt content: "test test test\n" */
> int main (int argc, char *argv [])
> {
>   with_open_file (in, "test2.txt", "r")
>   {
>     char *nextfilename = NULL;
>     size_t nextfilename_size = 0;
>     char **p = NULL;
>     nextfilename_size = getline (&nextfilename, &nextfilename_size, in);
>     nextfilename [--nextfilename_size] = 0;
>     printf ("[cat %s: [", nextfilename);
>     with_open_file (in, nextfilename, "r")
>     {
>       char **p = NULL;
>       char c = fgetc (in);
>       int life = 3;
>       while (c != EOF)
> 	{
> 	  putchar (c);
> 	  c = fgetc (in);
> 	  if (! (--life))
> 	    *p = "segfault!";
> 	}
>       printf ("]]\n");
>     }
>     raise (SIGSEGV);
>     *p = "segfault!";
>   }
>   return 0;
> }
> 
> /* with-open-file-semi-safe.c ends here. */
> 
> ·····@marc0:~/tmp$ gcc -Wall -Wno-unused -D_GNU_SOURCE -std=c99 with-open-file-semi-safe.c
> ·····@marc0:~/tmp$ # `-D_GNU_SOURCE' is for `getline' ...
> ·····@marc0:~/tmp$ ./a.out
> [cat test.txt: [tesok
> ok
> ·····@marc0:~/tmp$ 
> 
From: Marco Antoniotti
Subject: Re: macros
Date: 
Message-ID: <vLsVc.50$D5.17036@typhoon.nyu.edu>
Marco Parrone wrote:
> Marco Antoniotti on Thu, 19 Aug 2004 10:57:37 -0400 writes:
> 
> 
>>I am impressed :)  What do you do if the file already exists? :)  What
>>if it does not exist? :)
> 
> 
> Oops :) Cleanup code not executed and (sometimes) unnoticed corrupted
> program state :)
> 
> You choose the behavior using the `opentype' argument.
> 
> 1. If the existance or not existance is not compatible with the
> selected behavior, then fopen returns NULL, and NULL is stored into
> `name'.

Ok.  I guess I was being nasty asking for functionality that actually 
depends on open/fopen in both the C library and CL. :)

I think this was a cute exercise which taught me a couple of tricks 
thanks to C 'for'.

Not that I advocated that, of course. :)

Cheers
--
marco
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <87u0uxbflc.fsf@marc0.dyndns.org>
Marco Antoniotti on Fri, 20 Aug 2004 16:00:27 -0400 writes:

>>>I am impressed :)  What do you do if the file already exists? :)  What
>>>if it does not exist? :)
>> Oops :) Cleanup code not executed and (sometimes) unnoticed corrupted
>> program state :)
>> You choose the behavior using the `opentype' argument.
>> 1. If the existance or not existance is not compatible with the
>> selected behavior, then fopen returns NULL, and NULL is stored into
>> `name'.
>
> Ok.  I guess I was being nasty asking for functionality that actually
> depends on open/fopen in both the C library and CL. :)
>
> I think this was a cute exercise which taught me a couple of tricks
> thanks to C 'for'.

Me too, Stefan's examples of alternative uses of `for' were lighting,
and I learned about longjmp/setjmp and signal just to contrast your
points :)

However, as Marco Gidde pointed out I can not trap explicit returns
within the body, and as Frank and Stefan pointed out the gensym
"implementation" has many flaws.

Then, IMHO the only two ways to implement in C the two code-walking programs:

  1) ············@newsreader2.netcologne.de

  2) ··············@javamonkey.com

are:

  a) implement a (maybe partial) C intepreter (if you choose to
     strigify the source code and analyze it as a string)

  b) implement a (maybe partial) x86 (or whather is in use)
     interpreter (if you choose to get start and end addresses of the
     compiled code and analyze it)

I've tried first with `a' [x] [y], then I realized that it was not
going to be easy (neither the `check against blacklist of keywords'
nor the `check within whitelist of functions names' approaches were
going to give acceptable results), so I tried `b' [z], then I realized
that it was not going to be easy too (I tried to recognize a general
pattern for function calls, but then I realized that I needed to know
much more ASM than I do, for example because not all the instructions
have the same length, and because I had to distinguish code from data).

Here is what remains of the attempts, it is not finished (expecially
`z'), not correct (expecially `z') and not working (expecially `z'),
thay are only here to show how the attempts were made.

  x. http://www.geocities.com/marcoparrone/list-functions-called.c
  y. http://www.geocities.com/marcoparrone/list-functions-called-bin.c
  z. http://www.geocities.com/marcoparrone/list-function-calls.c

At last I agree (with all the peoples that pointed it out) that you
can do with Lisp macros things that you can not do with C macros, if
not implementing an emulation of what Lisp does `out of the box', and
so it has more to do with the full language, i.e. it's more a Lisp vs
C issue than a `defmacro' vs `#define' one.

Cheers,

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
 - going on unplugged vacation
From: Peter Herth
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <cfledi$i7u$1@newsreader2.netcologne.de>
Peter Seibel wrote:

> I think he's saying it's in general not possible to implement new
> control constructs in C. repeat/until is maybe not the best example to
> challenge C programmers with because of solutions like yours. But
> yours is still only a half solution since you are limited to textual
> substitution:

Yes, I was a little bit sloppy. If I had said "Java" I had not to worry
about nasty preprocessor trickses :).  But indeed my point was that there
is no general possibility to control your language.

Peter


-- 
pet project: http://dawn.netcologne.de
homepage:    http://www.peter-herth.de
lisp stuff:  http://www.peter-herth.de/lisp.html
get Ltk here: http://www.peter-herth.de/ltk/
From: Peter Herth
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <cflgmo$n3u$1@newsreader2.netcologne.de>
Stefan Ram wrote:

> Peter Herth <·····@netcologne.de> writes:
>>Yes, I was a little bit sloppy. If I had said "Java" I had not to worry
>>about nasty preprocessor trickses :).
> 
>   Yes, but then there is The Java Syntactic Extender:
> 
> http://jse.sourceforge.net/

Well, from a brief look this looks like a preprocessor application
that runs in front of the java compiler. Of course you can write
all kind of translators for your source code, that is almost
trivial. What I was talking about was modifying your language
with builtin stuff. So the C preprocessor barely counts, but
of course is very limited in its means.

Peter

-- 
pet project: http://dawn.netcologne.de
homepage:    http://www.peter-herth.de
lisp stuff:  http://www.peter-herth.de/lisp.html
get Ltk here: http://www.peter-herth.de/ltk/
From: Peter Herth
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <cflprn$cgs$1@newsreader2.netcologne.de>
Stefan Ram wrote:

>   So, I agree, that "Java" can not be modified with builtin
>   stuff like that,

That is the whole point. Whether a language allows its modification
with its on-board means.

> but if we shift the scope slightly to
>   "JSE+Java", it can be modified with builtin-stuff and JSE is
>   available to everyone who is using Java.

then we can do every transformation with every language. There
are Lisp->Java, Anything->C compilers around afterall. 

Peter

-- 
pet project: http://dawn.netcologne.de
homepage:    http://www.peter-herth.de
lisp stuff:  http://www.peter-herth.de/lisp.html
get Ltk here: http://www.peter-herth.de/ltk/
From: Bruce Stephens
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87smapsoh0.fsf@cenderis.demon.co.uk>
Marco Parrone <·····@autistici.org> writes:

[...]

> #include <stdio.h>
>
> /* repeat .. until: implementation #1: aliasing do ... while */
> /*
> #define repeat do {
> #define until } while
> */

I think that's repeat .. while (or even do .. while) rather than
repeat .. until.

[...]
From: Marco Parrone
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87brhdael7.fsf@marc0.dyndns.org>
Bruce Stephens on Sat, 14 Aug 2004 16:56:11 +0100 writes:

> Marco Parrone <·····@autistici.org> writes:
>
> [...]
>
>> #include <stdio.h>
>>
>> /* repeat .. until: implementation #1: aliasing do ... while */
>> /*
>> #define repeat do {
>> #define until } while
>> */
>
> I think that's repeat .. while (or even do .. while) rather than
> repeat .. until.

I think he was talking about implementing Pascal (language :D)
 `repeat ... until' in C.
From: Bruce Stephens
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87oeldsn85.fsf@cenderis.demon.co.uk>
Marco Parrone <·····@autistici.org> writes:

> Bruce Stephens on Sat, 14 Aug 2004 16:56:11 +0100 writes:
>
>> Marco Parrone <·····@autistici.org> writes:
>>
>> [...]
>>
>>> #include <stdio.h>
>>>
>>> /* repeat .. until: implementation #1: aliasing do ... while */
>>> /*
>>> #define repeat do {
>>> #define until } while
>>> */
>>
>> I think that's repeat .. while (or even do .. while) rather than
>> repeat .. until.
>
> I think he was talking about implementing Pascal (language :D)
>  `repeat ... until' in C.

But the test is backwards, isn't it?  Even in Pascal, I presume.

Something like

#define repeat do {
#define until(a) } while (!(a))

would be better, wouldn't it?
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <874qn5ac93.fsf_-_@marc0.dyndns.org>
Bruce Stephens on Sat, 14 Aug 2004 17:23:06 +0100 writes:

>>>> #include <stdio.h>
>>>>
>>>> /* repeat .. until: implementation #1: aliasing do ... while */
>>>> /*
>>>> #define repeat do {
>>>> #define until } while
>>>> */
>>>
>>> I think that's repeat .. while (or even do .. while) rather than
>>> repeat .. until.
>>
>> I think he was talking about implementing Pascal (language :D)
>>  `repeat ... until' in C.
>
> But the test is backwards, isn't it?  Even in Pascal, I presume.
>
> Something like
>
> #define repeat do {
> #define until(a) } while (!(a))
>
> would be better, wouldn't it?

Yes, thanks.
From: Alexander Kjeldaas
Subject: Re: macros
Date: 
Message-ID: <411E342F.1090603@fast.no>
Marco Parrone wrote:
> Peter Herth on Sat, 14 Aug 2004 09:34:04 +0200 writes:
> 
> 
>>Tayssir John Gabbour wrote:
>>
>>
>>>One place this is useful is to build a new control construct. Most
>>>languages announce a new 'for' loop as if they're bringing fire from
>>>the gods. In lisp, you simply create your 'for' macro and it can
>>>transform your sexp into a sexp with gotos or a 'do' loop. I mean, a
>>>'for' loop is so close to other loops in a language that there should
>>>be a way to represent one as another, without having all the nuts &
>>>bolts show.
>>
>>Well, this is for me the prime example, whenever I try to explain
>>why Lisp is so different from other language in one sentence. 
>>I ask people how they would implement a looping construct like
>>"for" in their language. (For example repeat...until for C programmers).
> 
> 
> Like this[1]?
> 
> Are you saying that's not possible to implement looping constructs in
> other languages (like C), or that it is going to be done in a
> different way?
> 

Good work.  Now try implementing a simple marco like the equivalent of

(repeat 10
    ...)

in standard C.  Try to make it portable and make it support nesting.

astor
From: Matthew Danish
Subject: Re: macros
Date: 
Message-ID: <20040815003358.GS15746@mapcar.org>
On Sat, Aug 14, 2004 at 04:17:28PM +0000, Stefan Ram wrote:
> Alexander Kjeldaas <··········@fast.no> writes:
> >(repeat 10
> >    ...)
> >in standard C.  Try to make it portable and make it support nesting.
> 
> #define repeat(i) for(int \
>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ = 0; \
>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ < (i); \
>   ++comp_lang_lisp_2004_08_14_18_10_40_02_00__ )

I haven't tried it, but I don't see how this can possibly support
nesting of repeat forms.  You need the equivalent of uninterned symbols,
gensym, or hygenic macros for that.

-- 
;;;; Matthew Danish -- user: mrd domain: cmu.edu
;;;; OpenPGP public key: C24B6010 on keyring.debian.org
From: Bruce Stephens
Subject: Re: macros
Date: 
Message-ID: <87vfflw7h8.fsf@cenderis.demon.co.uk>
Matthew Danish <·······@andrew.cmu.edu> writes:

> On Sat, Aug 14, 2004 at 04:17:28PM +0000, Stefan Ram wrote:
>> Alexander Kjeldaas <··········@fast.no> writes:
>> >(repeat 10
>> >    ...)
>> >in standard C.  Try to make it portable and make it support nesting.
>> 
>> #define repeat(i) for(int \
>>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ = 0; \
>>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ < (i); \
>>   ++comp_lang_lisp_2004_08_14_18_10_40_02_00__ )
>
> I haven't tried it, but I don't see how this can possibly support
> nesting of repeat forms.  You need the equivalent of uninterned symbols,
> gensym, or hygenic macros for that.

I think it'll work in C++.  (Possibly a recent standard C.)  C++ (and
C) have lexically scoped variables, and allow the possibility of inner
scopes shadowing outer ones.  So (in C++) things like this will work:

       for (int i=0; i<10; i++) {
           for (int i=10; i>0; i--) {
               ...
           }
       }
From: Matthew Danish
Subject: Re: macros
Date: 
Message-ID: <20040816161705.GA13999@mapcar.org>
On Sun, Aug 15, 2004 at 01:01:34AM +0000, Stefan Ram wrote:
> Matthew Danish <·······@andrew.cmu.edu> writes:
> >> #define repeat(i) for(int \
> >>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ = 0; \
> >>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ < (i); \
> >>   ++comp_lang_lisp_2004_08_14_18_10_40_02_00__ )
> >I haven't tried it, but I don't see how this can possibly support
> >nesting of repeat forms.  You need the equivalent of uninterned symbols,
> >gensym, or hygenic macros for that.
> 
>   The repeat-macro can be "nested", in the sense that
> 
> repeat(3)repeat(4)f();
> 
>   will call "f" 12 times, which follows from ISO/IEC 9899:1999
>   (E) (section 6.8.5, 6.2.1p4, and others)
> 
>   The language C is defined by ISO/IEC 9899:1999 (E), not by an
>   implementation, so it will not give an authoritative result to
>   "try it".

Ah, I missed the `int' in there.  Is that now legal in C?

-- 
;;;; Matthew Danish -- user: mrd domain: cmu.edu
;;;; OpenPGP public key: C24B6010 on keyring.debian.org
From: Alexander Kjeldaas
Subject: Re: macros
Date: 
Message-ID: <cflq6t$k5m$1@localhost.localdomain>
Stefan Ram wrote:
> Alexander Kjeldaas <··········@fast.no> writes:
> 
>>(repeat 10
>>   ...)
>>in standard C.  Try to make it portable and make it support nesting.
> 
> 
> #define repeat(i) for(int \
>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ = 0; \
>   comp_lang_lisp_2004_08_14_18_10_40_02_00__ < (i); \
>   ++comp_lang_lisp_2004_08_14_18_10_40_02_00__ )
> 

Two problems.  One is the obvious name space pollution problem that you 
did a very good effort of getting rid of :-)  The other is that the 
above is not legal C.  You have to define your variable outside the for(..).

> 
>   Some years ago, I invented two preprocessor macros for
>   resource management.
> 
>   In a function, three (for example) resources are to be
>   allocated. Then, some work is to be done using these
>   resources, and finally the resources are to be released.
> 
>   Moreover: should an attempt to allocate a resource fail, the
>   work cannot be done and exactly those resources that already
>   have been allocated successfully so far should be released.
>   Below, the operation "buffcopy" is just as an example of such a
>   work, which is using the resources, and not defined here.
>   If "buffcopy" is called, all three resources have be obtained
>   and will be released afterwards.
> 
>   The macros have been designed so that release actions appear
>   next to their corresponding obtain actions and a sequence of
>   multiple allocations does not require nesting to enhance
>   readability and maintainability. 
> 
> #include <stdlib.h>  /* malloc, free, EXIT_FAILURE */
> #include <stdio.h>   /* FILE, fopen, fclose, fread, fwrite */
> #include "example.h" /* buffcopy */
> 
> /* define TRY and PUSH here. */
> 
> int main( void )
> { int result = EXIT_FAILURE;
>   FILE * source; 
>   FILE * target; 
>   char * buffer;
>   TRY( source = fopen( "source", "r" ))
>   PUSH( fclose( source ))
>   TRY( target = fopen( "target", "w" ))
>   PUSH( fclose( target ))
>   TRY( buffer = malloc( 1024 ))
>   PUSH( free( buffer ))
>   result = buffcopy( target, source, buffer );
>   return result; }
> 
>   The definition of "TRY" and "PUSH" is left as an exercise to
>   the reader or might be revealed on request.
> 

This is very intriguing.  I can go most of the way, but I don't see how 
you manage to run the cleanup stuff between the two last lines.  In this 
special case we could use _atexit() though :-).  We're talking standard 
C here right?

astor
From: Alexander Kjeldaas
Subject: Re: macros
Date: 
Message-ID: <cflu69$m7j$1@localhost.localdomain>
Stefan Ram wrote:
> 
>   It is legal C according to the relevant C specification
>   ISO/IEC 9899:1999 (E), section 6.8.5. This ISO specification
>   contains the sentence:
> 
>       "This second edition cancels and replaces the first
>       edition, ISO/IEC 9899:1990"
> 
>   So ISO/IEC 9899:1990, which did not allow this declaration
>   inside of the for-parentheses, has been canceled by the ISO
>   many years ago.
>  

Of course you are right!  My compiler is obviously out of date.

> 
>>This is very intriguing.  I can go most of the way, but I don't see how 
>>you manage to run the cleanup stuff between the two last lines.  In this 
>>special case we could use _atexit() though :-).  We're talking standard 
>>C here right?
> 
> 
>   Yes. My solution is:
> 
> #define TRY(x) for(int try=1;(try&&(x));
> #define PUSH(y) ((try=0),(y)))
> 

Very nice, but also tricky!  You did not indicate that the last two 
lines were in different scopes.  As a user of these macros I would be 
surprised by this behaviour.

astor
From: Ivan Boldyrev
Subject: Re: macros
Date: 
Message-ID: <m7mlv1xmfe.ln2@ibhome.cgitftp.uiggm.nsc.ru>
On 8836 day of my life Alexander Kjeldaas wrote:
> Now try implementing a simple marco like the equivalent of
>
> (repeat 10
>     ...)
>
> in standard C.  Try to make it portable and make it support nesting.

All tasks are too simple.  It is just proper substitution and clever
usage of language features.

But C macros cannot perform tasks where arguments must be analyzed.
For example:

1.  Write code (maybe, in some Turing-complete sublanguage) and do
    type inference a-la ML/Haskell.
    
2.  Convert regexp to DFSM at compile time.  May be, you can implement
    NFSM with C macros, but it is slower than DFSM (AFAIK).

First task is implemented by me in Lisp.  Second one is implemented by
number of Lisp packages.

-- 
Ivan Boldyrev

       Assembly of a Japanese bicycle requires greatest peace of spirit.
From: Pascal Bourguignon
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87ekm9b09d.fsf@thalassa.informatimago.com>
Marco Parrone <·····@autistici.org> writes:

> Peter Herth on Sat, 14 Aug 2004 09:34:04 +0200 writes:
> 
> > Tayssir John Gabbour wrote:
> >
> >> One place this is useful is to build a new control construct. Most
> >> languages announce a new 'for' loop as if they're bringing fire from
> >> the gods. In lisp, you simply create your 'for' macro and it can
> >> transform your sexp into a sexp with gotos or a 'do' loop. I mean, a
> >> 'for' loop is so close to other loops in a language that there should
> >> be a way to represent one as another, without having all the nuts &
> >> bolts show.
> >
> > Well, this is for me the prime example, whenever I try to explain
> > why Lisp is so different from other language in one sentence. 
> > I ask people how they would implement a looping construct like
> > "for" in their language. (For example repeat...until for C programmers).
> 
> Like this[1]?
> 
> Are you saying that's not possible to implement looping constructs in
> other languages (like C), or that it is going to be done in a
> different way?


                                                               .---.
                                                              /  .  \
                                                             |\_/|   |
                                                             |   |  /|
  .----------------------------------------------------------------' |
 /  .-.                                                              |
|  /   \  AI koan --                                                 |
| |\_.  |                                                            |
|\|  | /| A student, in  hopes of understanding the Lambda-nature,   |
| `---' | came  to Greenblatt.   As  they spoke  a Multics  system   |
|       | hacker  walked by.   "Is  it true",  asked the  student,   | 
|       | "that PL-1  has many  of the same  data types  as Lisp".   | 
|       | Almost  before the  student had  finished  his question,   | 
|       | Greenblatt shouted,  "FOO!", and hit the  student with a   | 
|       | stick.                                                     | 
|       |                                                           /
|       |----------------------------------------------------------'
\       |
 \     /
  `---'

    
-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Our enemies are innovative and resourceful, and so are we. They never
stop thinking about new ways to harm our country and our people, and
neither do we.
From: Bruce Hoult
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <bruce-40A825.10491515082004@copper.ipg.tsnz.net>
In article <·················@marc0.dyndns.org>,
 Marco Parrone <·····@autistici.org> wrote:

> Are you saying that's not possible to implement looping constructs in
> other languages (like C), or that it is going to be done in a
> different way?
> 
> 1.
> 
> #include <stdio.h>
> 
> /* repeat .. until: implementation #1: aliasing do ... while */
> /*
> #define repeat do {
> #define until } while
> */

That will work in a way, largely because it's not doing anything new.  
But it isn't in any way defining proper syntax.  For example, there is 
no way to detect someone writing...

  repeat
    printf ("%d ", i);
    --i;
  } while (i != 0);

... instead of using your "until".

Oh, and btw, you didn't run your code before posting it.


> /* repeat ... until: implementation #2: using GCC local labels */
> /*
> #define repeat { __label__ loop; loop:
> #define until(cond) if (cond) goto loop; }
> */
> 
> /* repeat ... until: implementation #3: using GAS local labels */
> #define repeat __asm__ ("1:");
> #define until(cond) if (cond) __asm__ ("jmp 1b")

Neither of these is going to handle nested loops.

All your examples have the same problem that while a programmer *can* 
correctly match up your new macros, there is no way to check that they 
have.

You also haven't shown how to write a C macro coresponding to the given 
example, that expands to arbitrarily nested for loops, with the depth 
depending on the way the user uses the macro.

Common Lisp and Dylan and Scheme macros actually create new syntax and 
integrate it into the language so seamlessly that you can't tell it 
isn't built in.

That's no important when you're doing macros used to just one level, but 
when almost everything you do is a macro that expands to a macro that 
expands to a macro it is essential.

-- 
Bruce |  41.1670S | \  spoken |          -+-
Hoult | 174.8263E | /\ here.  | ----------O----------
From: Jeff
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <TqxTc.291300$JR4.238656@attbi_s54>
Bruce Hoult wrote:

> In article <·················@marc0.dyndns.org>,
>  Marco Parrone <·····@autistici.org> wrote:
> 
> > Are you saying that's not possible to implement looping constructs
> > in other languages (like C), or that it is going to be done in a
> > different way?
> > 
> > 1.
> > 
> > #include <stdio.h>
> > 
> > /* repeat .. until: implementation #1: aliasing do ... while */
> > /*
> > #define repeat do {
> > #define until } while
> > */
> 
> That will work in a way, largely because it's not doing anything new.
> But it isn't in any way defining proper syntax.  For example, there
> is no way to detect someone writing...
> 
>   repeat
>     printf ("%d ", i);
>     --i;
>   } while (i != 0);
> 
> ... instead of using your "until".
> 
> Oh, and btw, you didn't run your code before posting it.
> 
> 
> > /* repeat ... until: implementation #2: using GCC local labels */
> > /*
> > #define repeat { label loop; loop:
> > #define until(cond) if (cond) goto loop; }
> > */
> > 
> > /* repeat ... until: implementation #3: using GAS local labels */
> > #define repeat asm ("1:");
> > #define until(cond) if (cond) asm ("jmp 1b")
> 

Sorry for inserting here. I'm not necessarily replying to your post, as
opposed to getting into the discussion....

I'm actually quite suprised that everyone is still trying to compare
C/C++ macros (and other text preprocessor macro systems) to that of
Lisp. Simply put, there is no comparison. I think most people here know
this, and are just having a difficult time coming up with macros that
prove this.

The solution is quite simple: Lisp can evaluate DURING macro
exapansion. A preprocessor can't do that -- all it does is text
substitution.

For example, here is a perfectly good Lisp macro:

(defmacro foo (x)
  (if (numberp x) (format nil "~A" x) x))

What's the advantage here? Well, for the simple macro that it is, it
demonstrates that lisp can evaluate during *compile-time* and simplify
code greatly by doing so. There have been many cases that I've created
macros that have done something similar [to the above]. At
compile-time, I will know that 'x' is a string or a function or a
number, and I want to take a different action accordingly. Why do these
checks at runtime when I can just do them at compile time and generate
the proper code and inline it?

That is the power of the Lisp macro -- not generating code, not
creating strange loop segments and not even simplifying code by
generating code for you (most text preprocessors can do all of these).
The power is in executing code at compile-time to create
[con/ad]ditional code.

Jeff

-- 
I'm just beginning to grok Lisp; I can't even begin to imagine how much
more productive I'll be a month from now!
From: Marco Parrone
Subject: Re: macros (was: Paul Graham's teaching style is bad}
Date: 
Message-ID: <87fz6pp9ch.fsf@marc0.dyndns.org>
Bruce Hoult on Sun, 15 Aug 2004 10:49:15 +1200 writes:

> Oh, and btw, you didn't run your code before posting it.

Yes, I run it.  I just had not known `repeat ... until'.  I've never
seen it before, and I had misunderstood the description I found with a
little googling.  I've run the code befor posting.  All the code I
posted compile and run without errors nor warnings, running giving
meaningful output, with GCC 3.4.1.

>> /* repeat ... until: implementation #2: using GCC local labels */
>> /*
>> #define repeat { __label__ loop; loop:
>> #define until(cond) if (cond) goto loop; }
>> */
>> 
>> /* repeat ... until: implementation #3: using GAS local labels */
>> #define repeat __asm__ ("1:");
>> #define until(cond) if (cond) __asm__ ("jmp 1b")
>
> Neither of these is going to handle nested loops.

Yes, the first nests.  `myfor' nests too.  I fixed the
`repeat...until' error.

#include <stdio.h>

#define repeat { __label__ loop; loop:
#define until(cond) if (! (cond)) goto loop; }

int
main (int argc, char *argv[])
{
  int i;
  int k;

  k = 0;
  repeat
    i = 10;
    printf ("[%d:", k);
    repeat
      printf (" %d", i);
      --i;
    until (i == 0);
    printf ("]\n");
    k++;
  until (k == 10);

  printf ("\n");
  return 0;
}

·····@marc0:~/tmp$ gcc -Wall until.c
·····@marc0:~/tmp$ ./a.out
[0: 10 9 8 7 6 5 4 3 2 1]
[1: 10 9 8 7 6 5 4 3 2 1]
[2: 10 9 8 7 6 5 4 3 2 1]
[3: 10 9 8 7 6 5 4 3 2 1]
[4: 10 9 8 7 6 5 4 3 2 1]
[5: 10 9 8 7 6 5 4 3 2 1]
[6: 10 9 8 7 6 5 4 3 2 1]
[7: 10 9 8 7 6 5 4 3 2 1]
[8: 10 9 8 7 6 5 4 3 2 1]
[9: 10 9 8 7 6 5 4 3 2 1]

·····@marc0:~/tmp$ 


#include <stdio.h>

#define myfor(init, cond, step, body) { init; while (cond) { body; step; } }

int
main (int argc, char *argv[])
{
  int i;
  int j;

  myfor (i = 0,
	 i < 10,
	 ++i,
	 printf ("[%d:", i);
	 myfor (j = 10,
		j > 0,
		--j,
		printf (" %d", j));
	 printf ("]\n"));
  return 0;
}


·····@marc0:~/tmp$ gcc -Wall myfor.c
·····@marc0:~/tmp$ ./a.out
[0: 10 9 8 7 6 5 4 3 2 1]
[1: 10 9 8 7 6 5 4 3 2 1]
[2: 10 9 8 7 6 5 4 3 2 1]
[3: 10 9 8 7 6 5 4 3 2 1]
[4: 10 9 8 7 6 5 4 3 2 1]
[5: 10 9 8 7 6 5 4 3 2 1]
[6: 10 9 8 7 6 5 4 3 2 1]
[7: 10 9 8 7 6 5 4 3 2 1]
[8: 10 9 8 7 6 5 4 3 2 1]
[9: 10 9 8 7 6 5 4 3 2 1]
·····@marc0:~/tmp$ 

> All your examples have the same problem that while a programmer *can* 
> correctly match up your new macros, there is no way to check that they 
> have.

true, i just wanted to see if it can be done easily, not if it can be
done with checks and all that fancy things ;)

I find that the latest 2 challenges about walking the sources harder,
I don't think I can solve them, however I will try.

I like more the more explicit/detailed replies that I got in the
thread, than justing having to trust `this can not be done in C'.

> You also haven't shown how to write a C macro coresponding to the given 
> example, that expands to arbitrarily nested for loops, with the depth 
> depending on the way the user uses the macro.

Please let me see how it does not nest.  Please note that the `myfor'
macro definition is not changed.

> Common Lisp and Dylan and Scheme macros actually create new syntax and 
> integrate it into the language so seamlessly that you can't tell it 
> isn't built in.

> That's no important when you're doing macros used to just one level, but 
> when almost everything you do is a macro that expands to a macro that 
> expands to a macro it is essential.

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Abdulaziz Ghuloum
Subject: Re: macros
Date: 
Message-ID: <cfmamd$a41$1@hood.uits.indiana.edu>
Marco Parrone wrote:

> [...]
> Yes, the first nests.  `myfor' nests too.  I fixed the
> `repeat...until' error.
> 
> #include <stdio.h>
> 
> #define repeat { __label__ loop; loop:
> #define until(cond) if (! (cond)) goto loop; }
> 
> int
> main (int argc, char *argv[])
> {
>   int i;
>   int k;
> 
>   k = 0;
>   repeat
>     i = 10;
>     printf ("[%d:", k);
>     repeat
>       printf (" %d", i);
>       --i;
>     until (i == 0);
>     printf ("]\n");
>     k++;
>   until (k == 10);
> 
>   printf ("\n");
>   return 0;
> }
> 
> ·····@marc0:~/tmp$ gcc -Wall until.c
> ·····@marc0:~/tmp$ ./a.out
> [0: 10 9 8 7 6 5 4 3 2 1]
> [1: 10 9 8 7 6 5 4 3 2 1]
> [2: 10 9 8 7 6 5 4 3 2 1]
> [3: 10 9 8 7 6 5 4 3 2 1]
> [4: 10 9 8 7 6 5 4 3 2 1]
> [5: 10 9 8 7 6 5 4 3 2 1]
> [6: 10 9 8 7 6 5 4 3 2 1]
> [7: 10 9 8 7 6 5 4 3 2 1]
> [8: 10 9 8 7 6 5 4 3 2 1]
> [9: 10 9 8 7 6 5 4 3 2 1]
> 
> ·····@marc0:~/tmp$ 
> 
> 

[/tmp]: gcc -Wall until.c
until.c: In function `main':
until.c:16: error: duplicate label declaration `loop'
until.c:13: error: this is a previous declaration
until.c:16: error: duplicate label `loop'

[/tmp]: gcc -v
Reading specs from /usr/libexec/gcc/darwin/ppc/3.3/specs
Thread model: posix
gcc version 3.3 20030304 (Apple Computer, Inc. build 1666)
From: Marco Parrone
Subject: Re: macros
Date: 
Message-ID: <878ychp72z.fsf@marc0.dyndns.org>
Abdulaziz Ghuloum on Sat, 14 Aug 2004 19:27:56 -0500 writes:

>> #define repeat { __label__ loop; loop:
>> #define until(cond) if (! (cond)) goto loop; }

>> ·····@marc0:~/tmp$ gcc -Wall until.c
>> ·····@marc0:~/tmp$ ./a.out

> [/tmp]: gcc -Wall until.c
> until.c: In function `main':
> until.c:16: error: duplicate label declaration `loop'
> until.c:13: error: this is a previous declaration
> until.c:16: error: duplicate label `loop'
>
> [/tmp]: gcc -v
> Reading specs from /usr/libexec/gcc/darwin/ppc/3.3/specs
> Thread model: posix
> gcc version 3.3 20030304 (Apple Computer, Inc. build 1666)


·····@marc0:~/tmp$ gcc -v
Reading specs from /opt/gcc/lib/gcc/i686-pc-linux-gnu/3.4.1/specs
Configured with: ./configure --prefix=/opt/gcc
Thread model: posix
gcc version 3.4.1
·····@marc0:~/tmp$ 

That's the feature that is not working in the same way:

  http://gcc.gnu.org/onlinedocs/gcc-3.4.1/gcc/Local-Labels.html#Local%20Labels

-- 
Marco Parrone <·····@autistici.org> [0x45070AD6]
From: Bruce Hoult
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <bruce-A4D755.21550414082004@copper.ipg.tsnz.net>
In article <············@newsreader2.netcologne.de>,
 Peter Herth <·····@netcologne.de> wrote:
> Well, this is for me the prime example, whenever I try to explain
> why Lisp is so different from other language in one sentence. 
> I ask people how they would implement a looping construct like
> "for" in their language. (For example repeat...until for C programmers).
> In Lisp I can :) Acutally I implemented a C-style for for lisp, so for
> those interested here it is. (it is actually in scheme (Kawa), but as it
> uses defmacro and backquote the translation to Common Lisp should be
> simple)
> 
> ;; helper function
> 
> (define (for-expand defs body)
>   (let ((def (car defs)))
>     (if (list? def)
>         (let ((rest-def (rest defs)))
>           `(do ((,(first def) ,(second def) ,(fourth def)))
>                ((not ,(third def)))
>              ,(if (not (null? rest-def))
>                   (for-expand rest-def body)
>                   `(begin ,@body))))
>           `(do ((,(first defs) ,(second defs) ,(fourth defs)))
>                ((not ,(third defs)))
>              ,@body))))
> 
> ;; macro definition
> (defmacro for (defs . body)
>   (for-expand defs body))
> 
> ;; sample usage, single loop
> (define (test2)
>   (for (i 0 (< i 10) (+ i 1))
>        (display i)
>        (newline)))
> 
> ;; but it also enables any number of cascded loops with one construct,
> ;; here we iterate over a "cube" of numbers
> 
> (define (test3)
>   (for ((i 0 (< i 5) (+ i 1))
>         (j 2 (< j 7) (+ j 1))
>         (k 3 (< k 5) (+ k 1)))
>        (display i)
>        (display " ")
>        (display j)
>        (display " ")
>        (display k)
>        (newline)))

Not a bad example, and a good implementation of it, except:

- the third (increment) item in a C for loop is a statement, not an 
expression that is implicitly the new value for the control variable.

- C++ allows more than one loop variable separated by commas as long as 
they are all of the same base type.

- C allows more than one step statement, also seperated by commas.

- you made no attempt to emulate the syntax of C, so you've ended up 
pretty much with just a scheme "do" loop with a slightly different 
ordering of the subexpressions.


Here's my attempt in Dylan.

It does everything yours does, plus looks more like C and uses the C 
distinction of ; vs , to allow multiple loop variables and multiple 
stepping statements.  I've also been careful to allow the classic C 
idiom of leaving out any or all of the parts e.g. "c-for(;;) ... end".  
In particular, a missing test is the same as "true".

Unlike C I don't put { } around the body of the loop.  In fact that 
would be trivial -- just put { and } in the obvious place in the base 
case for nested-loops -- but Dylan macro syntax rules will still require 
an "end" after the closing brace, which rather makes it pointless.

Oh, yes, and mine also allows optional type declarations on the control 
variables.  The built-in pattern type ?:variable matches either "name" 
or "name :: type".

There are several ways in which I could have better matched C but chose 
not to for reasons of good taste (and in fact I implemented and tested 
them and then took them out again).

- I could have made control variable type declarations come before the 
variable name, as in C.

- if the type declaration was missing then I could have made the 
initialization into a Dylan assignment ":=", which would fail to compile 
unless the variable had been previously declared.


module: c-for-example

define macro c-for
  { c-for ?nested-loops end } => { ?nested-loops }

    nested-loops:
    { ( ?inits ; ?test ; ?increments ) ... }
    => { begin
           ?inits;
           local method step()
             if (?test) ... ; ?increments; step() end
           end;
           step()
         end }
    { ?:body } => { ?body }

    inits:
    { ?:variable = ?init:expression, ... }
    => { let ?variable = ?init; ... }
    {} => { #f }

    test:
    { ?:expression } => { ?expression }
    {} => { #t }

    increments:
    { ?increment:expression, ... } => { ?increment; ... }
    {} => {}
end c-for;

begin
  c-for (i = 0, j :: <float> = 10.0;
         i < 10;
         i := i + 1, j := j + 0.01)
    format-out("%d %=\n", i, j);
  end;

  c-for (i = 0; i < 5; i := i + 1)
        (j = 2; j < 7; j := j + 1)
        (k = 3; k < 5; k := k + 1)
    format-out("%d ", i);
    format-out("%d ", j);
    format-out("%d\n", k);
  end c-for;
end

-- 
Bruce |  41.1670S | \  spoken |          -+-
Hoult | 174.8263E | /\ here.  | ----------O----------
From: Jens Axel Søgaard
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <411d40dd$0$298$edfadb0f@dread11.news.tele.dk>
Kevin Clancy wrote:
> On Lisp - 7.1
> "Many languages offer some form of macro, but Lisp macros are singularly
> powerful. When a file of Lisp is compiled, a parser reads the source code
> and sends its output to the compiler. Here's the stroke of genius: the ouput
> of the parser consists of lists of Lisp objects. With macros, we can
> manipulate the program while it's in this intermidiate form between parser
> and compiler."
> 
> Gee. What a revelation. After about a half hour of contemplation, I came to
> the conclusion that what he was trying to say was that you can use Lisp to
> program the preprocessor.
> 
> That's cool. Unfortunately, Graham's excitement did not carry over to me as
> the reader. I have some sort of an intuitive idea of a Lisp object as
> anything enclosed by a "(" and a ")", although I do not beleive that was
> ever explicity stated in either "On Lisp" or Winston & Horn's book.

"On Lisp" was not meant as a first book on lisp, which is why Graham
takes this for granted.

> What I need is a more detailed explanation. Obviously, since Graham isn't
> telling the reader everything that he knows, can anyone point me to some
> resources that Graham may have used to gain his unrestrainable enthusiasm
> for this language?

Certainly. The various "Roads to Lisp" describes why people
switch to Lisp.

<http://alu.cliki.net/RtL%20Highlight%20Film>

-- 
Jens Axel Søgaard
From: mikel
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <yPiTc.6332$QM1.1482@newssvr29.news.prodigy.com>
Kevin Clancy wrote:
> On Lisp - 7.1
> "Many languages offer some form of macro, but Lisp macros are singularly
> powerful. When a file of Lisp is compiled, a parser reads the source code
> and sends its output to the compiler. Here's the stroke of genius: the ouput
> of the parser consists of lists of Lisp objects. With macros, we can
> manipulate the program while it's in this intermidiate form between parser
> and compiler."
> 
> Gee. What a revelation. After about a half hour of contemplation, I came to
> the conclusion that what he was trying to say was that you can use Lisp to
> program the preprocessor.

Not exactly. A C preprocessor operates on source tokens. A Lisp macro 
operates on the abstract syntax tree produced by parsing the source 
tokens. A C preprocessor can replace a token (or a simple pattern of 
tokens) with some other tokens. A Lisp macro can perform arbitrary 
computations on the input syntax tree, using the full power of the 
language and runtime, and the input it operates on is a structured 
syntax tree represented as a Lisp list, not a stream of characters or 
tokens. You could in theory make a C preprocessor do anything that can 
be done in C, but if you want to go beyond what the typical preprocessor 
does, you pretty much have to write a new preprocessor. Lisp's macro 
facility is out of the box able to easily do anything to the input tree 
that Lisp can do to lists, which is quite a lot.


> That's cool. Unfortunately, Graham's excitement did not carry over to me as
> the reader. I have some sort of an intuitive idea of a Lisp object as
> anything enclosed by a "(" and a ")", although I do not beleive that was
> ever explicity stated in either "On Lisp" or Winston & Horn's book.

It's surprisingly hard to explain what macros can do and why they are 
different from something like a preprocessor.

> So at this point, I'm guessing that the advantage of Lisp macros only comes
> when compilation takes places in the midst of your program... I'm confused.

The advantage appears any place where you want to build new syntax to 
make the inconvenient convenient.

For example, there are a zillion WITH-FOOBAR macros floating around in 
Lisp, but a rarely see anything like them elsewhere. They're very handy. 
WITH-OPEN-FILE is one that is built into the language standard.

(with-open-file (in "/my/path/name" :direction :input)
   (do-some-file-stuff in))

This form arranges to open the file and guarantees that it will be 
safely closed no matter how control exits from the stuff inside it.

OpenMCL uses a similar approach to manage various kinds of unsafe 
foreign storage, for example:

(with-cstrs ((foo "foo")
              (bar "bar"))
   (do-something-with-c-strings foo bar))

This form stack-allocates two C strings (presumably for use with some 
foreign library code), and of course disposes of them when the form exits.

Macros are also often used to turn complicated collections of primitives 
into convenient forms. For example, macros like DOTIMES and DOLIST are 
syntactic sugar for more primitive forms that set up initial conditions, 
sequences of forms to iterate, and tests to determine when iteration is 
done. They two common styles of iteration seem simpler than they really 
are under the covers:

(dotimes (i some-number-of-times-to-repeat)
   (do-stuff i))

(dolist (item some-items)
   (do-something-with-item item))

These are pretty convenient, but what is really convenient is that you 
can easily custom-make your own whenever you need them.

Macros are also used to build up custom or application-specific 
languages within Lisp. If Lisp didn't have IF or LET*, you could easily 
use macros to build them. A typical, fairly easy example that is 
sometimes used is to build a parenthesized version of Prolog syntax, 
which is slightly more involved than it at first appears, because 
Prolog's evaluation rules are quite different from Lisp's. Nevertheless, 
you can do it pretty easily because Macros enable you to control exactly 
when and how various parts of an expression are evaluated.


> What I need is a more detailed explanation. Obviously, since Graham isn't
> telling the reader everything that he knows, can anyone point me to some
> resources that Graham may have used to gain his unrestrainable enthusiasm
> for this language?

I notice Peter pointed you at his book. Seems like a good place to start.
From: matt knox
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <abbfde83.0408141413.3886526e@posting.google.com>
> It's surprisingly hard to explain what macros can do and why they are 
> different from something like a preprocessor.

You know, this is absolutely true, and is one of the reasons I don't
get to use as much lisp at work as I would like.  If I were able to
say, in a sentence or 3, why macros are a big deal, I would be allowed
to use them more.

My present best effort:

"Macros allow me to easily create a specialized language, without the
overhead of writing or executing an interpreter.  They can also give
me control of the semantics of the language, so I can do things that
just cannot be done otherwise."

This is not bad, but really does not cut it-in part because it begs a
bunch of questions:
Why is a specialized language good?
What are semantics?  (I would have trouble producing a really good
definition myself-my best guess is "the meaning of examples in a
language")
And the biggest one: what other practical application cannot be done
(well) without macros?

I thought I had an answer for this one from Graham:
(http://lib1.store.vip.sc5.yahoo.com/lib/paulgraham/bbnexcerpts.txt,
see "Closures Simulate Subroutines", about 3/4 of the way down if
you're impatient).  He talks about how lexical closures with macros
can simulate subroutines for web-programming.  When I showed it to a
very bright guy I know who has done a ton of lisp, but abandoned it
for PHP, he said that it was easy to do what Graham describes in PHP,
but that at the time Graham did it, lisp may have been the only way to
go, as PHP was not yet mature.

I am puzzled by the fact that lispers tend to be expressive and
bright, but cannot seem to come up with a good example of why the few
remaining distinctive features of lisp are a good thing.  Does this
just say something about the difficulty of the problems that are
heavy-duty enough to require macros, or is it that the stuff other
languages have been picking up from lisp for so long was the big deal,
and that macros are only marginally important by comparison, or is it
something entirely different?
From: Pascal Bourguignon
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <87657lcprz.fsf@thalassa.informatimago.com>
···········@gmail.com (matt knox) writes:

> > It's surprisingly hard to explain what macros can do and why they are 
> > different from something like a preprocessor.
> 
> You know, this is absolutely true, and is one of the reasons I don't
> get to use as much lisp at work as I would like.  If I were able to
> say, in a sentence or 3, why macros are a big deal, I would be allowed
> to use them more.
> [...]
> I am puzzled by the fact that lispers tend to be expressive and
> bright, but cannot seem to come up with a good example of why the few
> remaining distinctive features of lisp are a good thing.  Does this
> just say something about the difficulty of the problems that are
> heavy-duty enough to require macros, or is it that the stuff other
> languages have been picking up from lisp for so long was the big deal,
> and that macros are only marginally important by comparison, or is it
> something entirely different?

But that's because actually, lisp macros don't matter at all for 99%
of the programs.

Closures either don't matter at all for 99% of the programs.

Neither does run-time compilation matter at all for 99% of the programs.

Neither does any other distinguishing or not so distinguishing feature
of lisp.


The point is that it's the mix of all these features that is much more
than all of them taken indenpendantly, the fact that they're all
available at once makes a quantum jump to another level of programming
expressiveness.


You can get 90% of lisp macros with C macros.
You can get 90% of lisp GC with Java GC.
You can get 90% of lisp closures with ML closures.
You can get 90% of run-time compilation with perl.
You can get 90% of lisp sexp with Yacc.
You can even get 90% of mixing lisp macros and closures with PHP.

But there's only one language where you have all the expressive power
at hand: lisp.


There's also another point for the macros.

I've got the impression that declarative languages have a difficulty:
they need to incorporate potentially all the data structures and
algorithms you ever will implement.  If you want to declare something
that the declarative language does not allow you to express, you can't.

(You'd need a human or a good AI to process all declarative programs
ever).

However, declarative programming is still a good thing, because it's
much higher level programming than anything else. 

That's where lisp macros enter the scene: you can now use declarative
programming for any thing.  Once you've written your declarations in
sexps, there remains only to write a couple of macro to implement the
algorithms needed to process these declarations.  Note that between
the two steps, the status of the sexps you've written change!  First,
it's (declarative) source code.  Next, it's pure data. 


-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Our enemies are innovative and resourceful, and so are we. They never
stop thinking about new ways to harm our country and our people, and
neither do we.
From: David
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <ckxTc.134116$28.18208@fe1.news.blueyonder.co.uk>
Pascal Bourguignon wrote:

> ···········@gmail.com (matt knox) writes:
> 
> 
>>>It's surprisingly hard to explain what macros can do and why they are 
>>>different from something like a preprocessor.
>>
>>You know, this is absolutely true, and is one of the reasons I don't
>>get to use as much lisp at work as I would like.  If I were able to
>>say, in a sentence or 3, why macros are a big deal, I would be allowed
>>to use them more.
>>[...]
>>I am puzzled by the fact that lispers tend to be expressive and
>>bright, but cannot seem to come up with a good example of why the few
>>remaining distinctive features of lisp are a good thing.  Does this
>>just say something about the difficulty of the problems that are
>>heavy-duty enough to require macros, or is it that the stuff other
>>languages have been picking up from lisp for so long was the big deal,
>>and that macros are only marginally important by comparison, or is it
>>something entirely different?
> 
> 
> But that's because actually, lisp macros don't matter at all for 99%
> of the programs.
> 
> Closures either don't matter at all for 99% of the programs.
> 
> Neither does run-time compilation matter at all for 99% of the programs.
> 
> Neither does any other distinguishing or not so distinguishing feature
> of lisp.
> 
> 
> The point is that it's the mix of all these features that is much more
> than all of them taken indenpendantly, the fact that they're all
> available at once makes a quantum jump to another level of programming
> expressiveness.
> 
> 
> You can get 90% of lisp macros with C macros.
> You can get 90% of lisp GC with Java GC.
> You can get 90% of lisp closures with ML closures.
> You can get 90% of run-time compilation with perl.
> You can get 90% of lisp sexp with Yacc.
> You can even get 90% of mixing lisp macros and closures with PHP.
> 
> But there's only one language where you have all the expressive power
> at hand: lisp.
> 
> 
> There's also another point for the macros.
> 
> I've got the impression that declarative languages have a difficulty:
> they need to incorporate potentially all the data structures and
> algorithms you ever will implement.  If you want to declare something
> that the declarative language does not allow you to express, you can't.
> 
> (You'd need a human or a good AI to process all declarative programs
> ever).
> 
> However, declarative programming is still a good thing, because it's
> much higher level programming than anything else. 
> 
> That's where lisp macros enter the scene: you can now use declarative
> programming for any thing.  Once you've written your declarations in
> sexps, there remains only to write a couple of macro to implement the
> algorithms needed to process these declarations.  Note that between
> the two steps, the status of the sexps you've written change!  First,
> it's (declarative) source code.  Next, it's pure data. 
> 
> 
Indeed. I've started using Lisp fairly recently, and I've come to 
realise that macros are _immensely_ powerful. Here's an example...

Consider that you needed to do some XML transformation. You could use 
XSLT (a declarative language) which is pretty good, and convenient, for 
some XML tranformation tasks. If this does everything you need then 
fine, but you may well come across something which it can't do and then 
you're stuck - you've got to find something else to use. With most 
general purpose programming languages you'd lose the nice way of 
expressing transformations that XSLT gives you when you do this.

If you know lisp you probably wouldn't consider using XSLT, but you 
_might_ decide to use the way it represents transformations and 
implement it in lisp. That way you would still have the convenience of 
expression of XSLT, but its limitations wouldn't be there - you have the 
full power of lisp available and can go beyond the XSLT model whenever 
required.

I've done XML transformation in Lisp and it's _much_ nicer than doing it 
in other languages. The problem is until you've used lisp macros for a 
significant problem it's hard to appreciate how useful they are.
From: Kenny Tilton
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <wuyTc.53131$oW6.13277568@twister.nyc.rr.com>
matt knox wrote:

>>It's surprisingly hard to explain what macros can do and why they are 
>>different from something like a preprocessor.
> 
> 
> You know, this is absolutely true, and is one of the reasons I don't
> get to use as much lisp at work as I would like.  If I were able to
> say, in a sentence or 3, why macros are a big deal...

I doubt that is possible unless your audience already knows why macros 
are a big deal. A hardcore developer in some other language won't get it 
from a sound bite.

otoh, I could drag along my source code and provide three or six cool 
things I have been able to get done thx only to macros and everyone 
would get it, because, well, it's just obvious stuff any developer would 
grok.

of course someone would argue "I could do that without macros!", but 
their alternative would essentially be some poor-man's macro substitute, 
effectively arguing for macros.

, I would be allowed
> to use them more.

Lisp is not just macros. It is lexical scope, special variables, CLOS, 
compilation to native code, dynamic programming, bignums, etc etc etc.

> 
> My present best effort:
> 
> "Macros allow me to easily create a specialized language, without the
> overhead of writing or executing an interpreter.  They can also give
> me control of the semantics of the language, so I can do things that
> just cannot be done otherwise."
> 
> This is not bad, but really does not cut it-in part because it begs a
> bunch of questions:
> Why is a specialized language good?

Forget "specialized language", think "clean syntax" and "fewer bugs" and 
"less gruntwork". Any interesting application consists of more or less 
elaborate little subsets of code which implement some subset of the 
applications mechanics. These mechanisms have their own little APIs, if 
you will, with more or less plumbing/wiring/boilerplate needed to drive 
them.

Without macros, you get exposed wiring high and low. It is work getting 
that wiring right all the time, and it is easy to screw up the wiring, 
usually by cutting and pasting it and then neglecting to transform the 
clone completely. And should the mechanism get refactored and the 
necessary wiring turn out different -- well, that is why languages 
without macros need refactoring tools, because it is a total PITA to 
revise all that. (And now it is time to remember what Graham said about 
Lisp being especially useful when one does not know how to solve the 
problem one is trying to solve.) With macros one can hide wiring.

Macros are also good for generating mechanisms. I have ported Cells to 
other languages, but the amount of boilerplate around every class and 
slot is ridiculous without macros. With macros, I create a defclass-like 
macro -- same syntax and it does expand to the obvious defclass, but it 
also expands to all the boilerplate needed to make the Cells mechanism work.

> What are semantics?  (I would have trouble producing a really good
> definition myself-my best guess is "the meaning of examples in a
> language")
> And the biggest one: what other practical application cannot be done
> (well) without macros?

You should see how I generate FFI bindings for all those libraries used 
by Cello. :)

> 
> I thought I had an answer for this one from Graham:
> (http://lib1.store.vip.sc5.yahoo.com/lib/paulgraham/bbnexcerpts.txt,
> see "Closures Simulate Subroutines", about 3/4 of the way down if
> you're impatient).  He talks about how lexical closures with macros
> can simulate subroutines for web-programming.  When I showed it to a
> very bright guy I know who has done a ton of lisp, but abandoned it
> for PHP, he said that it was easy to do what Graham describes in PHP,
> but that at the time Graham did it, lisp may have been the only way to
> go, as PHP was not yet mature.
> 
> I am puzzled by the fact that lispers tend to be expressive and
> bright, but cannot seem to come up with a good example of why the few
> remaining distinctive features...

Few? No, other languages have this feature or that. What language by 
itself do you think has caught up with Lisp?

>... of lisp are a good thing.  Does this
> just say something about the difficulty of the problems that are
> heavy-duty enough to require macros, or is it that the stuff other
> languages have been picking up from lisp for so long was the big deal,
> and that macros are only marginally important by comparison, or is it
> something entirely different?

The problem is you. :) For one, you have fixated on macros. It is 
probably the first thing that pops into a Lispnik's mind, but that does 
not make it the only reason to use Lisp.

Second, you do not use macros yourself, so the light cannot go on for 
you. I made the analogy recently of the laser -- no one had a clue what 
to do with the now-ubiquitous tool when it was forst invented. You are 
trying to sell management on "a machine that goes PING".

I suggest you partner with a strong, local Lispnik willing to evangelize 
a little so you can jumpstart the process, but most of all I suggest you 
go write some Lisp.

kt

-- 
Cells? Cello? Celtik?: http://www.common-lisp.net/project/cells/
Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film
From: Pascal Costanza
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <cfm70h$avh$1@newsreader2.netcologne.de>
matt knox wrote:

> I am puzzled by the fact that lispers tend to be expressive and
> bright, but cannot seem to come up with a good example of why the few
> remaining distinctive features of lisp are a good thing.  Does this
> just say something about the difficulty of the problems that are
> heavy-duty enough to require macros, or is it that the stuff other
> languages have been picking up from lisp for so long was the big deal,
> and that macros are only marginally important by comparison, or is it
> something entirely different?

a) We don't need macros. We can program everything in assembler. It's 
important to keep in mind that all programming languages only and purely 
make things convenient, not possible. It's already possible to program 
anything in any language, so there's nothing to gain here.

The important gain of macros is that they allow you to remove 
boilerplate code. There are other means to remove boilerplate code, but 
few are as effective and convenient as (structural) macros.

b) It's hard to illustrate features of a language that tend to show 
their strength only in large programs.

c) One clear sign that languages are missing macros (or some such) is 
the fact that they are changed so often to include new features, 
sometimes in ways that are not backwards compatible to previous versions 
of those languages.

Of course, this is bad news for Lisp from a publicity point of view. 
Whereas other languages can make a big deal from adding little features, 
backed by long-winded review processes, sometimes cancelled by random 
decisions from management, then later reintroduced because of pressure 
from a competitor, and so forth, Lispers can just implement their own 
version of what they actually need now and move ahead. No press 
releases, no articles in computer magazines that give you an "insider's 
view" of the new breakthrough foreach statement, no keynote talks at 
conferences about metadata, no big error-prone frameworks that implement 
naive and slow interpreters (instead of embedded compilers!) for 
XML-based DSLs , no aspect-oriented extensions that try to give you some 
little more power back that others have taken from you, no Eclipse 
conference that everybody attends just because they fear Microsoft, and 
so forth. Just a few lines of Lisp code. That's it. Not enough to make a 
big deal out of it.

Actually, I think this is one reason why "worse is better". The worse 
stuff gets more publicity because their users need more information 
about how to work around inherent limitations.


Pascal

-- 
Tyler: "How's that working out for you?"
Jack: "Great."
Tyler: "Keep it up, then."
From: Tomasz Zielonka
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <slrnci8pje.p3s.t.zielonka@zodiac.mimuw.edu.pl>
Pascal Costanza wrote:
> a) We don't need macros. We can program everything in assembler. It's 
> important to keep in mind that all programming languages only and purely 
> make things convenient, not possible. It's already possible to program 
> anything in any language, so there's nothing to gain here.

It depends on what program properties you want to achieve. If you only
care about correctness and efficiency, then yes, everything that's
possible to do in Lisp is also possible to do in assembler. But if you
also care about a conciseness, clearity, maintainability, simplicity,
affordability, etc. then some things can be no longer possible to do in
assembler.

> The important gain of macros is that they allow you to remove 
> boilerplate code. There are other means to remove boilerplate code, but 
> few are as effective and convenient as (structural) macros.

I would say that first-class, higher-order functions are almost as
effective. It is interesting that almost all examples of macros given in
chapter ,,Macros: Standard Control Structures'' of upcoming Peter
Seibel's book can be easily implemented using HOFs in a lazy functional
language like Haskell. Of course there are applications of macros that
are not possible to do with HOFs alone - that's why people are working
on a macro system for Haskell.

I think that HOF approach has many advantages over macros, like this is
a uniform solution, without the need to introduce thousands of new
syntaxes.

There is something that bothers me in the Lisp community. Many of you
seem to neglect the possibility that other language communities can
have good reasons to do things the other way. I agree that there are
many particular bad examples, but try not to generalize this to all
non-lispy languages. Keep your minds open ;)

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
From: Rahul Jain
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <87vffafuho.fsf@nyct.net>
Tomasz Zielonka <··········@zodiac.mimuw.edu.pl> writes:

> I think that HOF approach has many advantages over macros, like this is
> a uniform solution, without the need to introduce thousands of new
> syntaxes.

The purpose of adding a macro is because the author _wants_ a new syntax
to clearly describe _what_ he wants done in his program, not _how_ he
wants it done. It is a rather common implementation technique to have
simple macros expand to HOF usages.

(declaim (inline call-with-foo))
(defun call-with-foo (... continuation)
  ...
  (funcall continuation)
  ...)

(defmacro with-foo (... &body body)
  (call-with-foo ... (lambda () ,@body)))

-- 
Rahul Jain
·····@nyct.net
Professional Software Developer, Amateur Quantum Mechanicist
From: Rob Warnock
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <QLudnTVVsOBVarfcRVn-uQ@speakeasy.net>
[Sorry for late response...]

Pascal Costanza  <········@web.de> wrote:
+---------------
| a) We don't need macros. We can program everything in assembler.
+---------------

Please don't assume this is an either/or choice! There *are* (or at
least, historically, have been) assemblers which had very close to
DEFMACRO-like capabilities -- MACRO-10 (the assembler for the PDP-10)
is a sterling example. Macros in MACRO-10 could do compile-time looping
and branching, could tear apart lists of arguments and individual
arguments (considered as lists of characters), could generate new
symbols based on arguments provided, could define/set/modify compile-time
variables (including those whose names were generated by macros),
and since MACRO-10 was a two-pass assembler that provided the ".if1"
and ".if2" tests, macros could gather information during pass one
(storing it in compile-time variables/symbols) and during pass two
emit local code chosen based on the *global* contents of the program!

I have written elsewhere [Google: FOCAL MACRO-10 rpw3] how useful
this is for writing lexical and syntax analysers, but it's also
useful for building complex graphs of objects at compile time,
planting all the needed links (pointers) between them with no
need for run-time initialization of the data structures.

+---------------
| It's important to keep in mind that all programming languages only
| and purely make things convenient, not possible. It's already possible
| to program anything in any language, so there's nothing to gain here.
+---------------

Don't discount "convenience", which has a very real value in
accelerating development and simplifying the code and thus
lowering both the initial and the ongoing maintenance costs!

+---------------
| The important gain of macros is that they allow you to remove 
| boilerplate code. There are other means to remove boilerplate code,
| but few are as effective and convenient as (structural) macros.
+---------------

While macros for boilerplate code are certainly part of it, to me
an equally-important part is allowing the programmer to decide --
right in their source code -- which parts of the computation are
to be done at compile time (well, macroexpansion time) and which
are deferred to runtime.

These two aspects work together, as for things mentioned above.
E.g., a DEFOPERATOR macro can provide convenient boilerplate for
defining some operator and related attributes, but at the *same*
time it can insert information about the operator into data structures
that are later available to the program, e.g., a symbol table, an
operator-precedence table, a code-to-emit table, etc.

+---------------
| b) It's hard to illustrate features of a language that tend to show 
| their strength only in large programs.
...
| Of course, this is bad news for Lisp from a publicity point of view. 
+---------------

Yes. (*sigh*)


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Christopher C. Stacy
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <uisb8ftzs.fsf@news.dtpq.com>
>>>>> On Tue, 24 Aug 2004 03:09:44 -0500, Rob Warnock ("Rob") writes:

 Rob> [Sorry for late response...]
 Rob> Pascal Costanza  <········@web.de> wrote:
 Rob> +---------------
 Rob> | a) We don't need macros. We can program everything in assembler.
 Rob> +---------------

 Rob> Please don't assume this is an either/or choice!

I used to write a fair amount of Lisp code mixed with assembler 
code on the PDP-10.
From: David Steuber
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <87657h3z7x.fsf@david-steuber.com>
mikel <·····@evins.net> writes:

> Not exactly. A C preprocessor operates on source tokens. A Lisp macro
> operates on the abstract syntax tree produced by parsing the source
> tokens. A C preprocessor can replace a token (or a simple pattern of
> tokens) with some other tokens. A Lisp macro can perform arbitrary
> computations on the input syntax tree, using the full power of the
> language and runtime, and the input it operates on is a structured
> syntax tree represented as a Lisp list, not a stream of characters or
> tokens. You could in theory make a C preprocessor do anything that can
> be done in C, but if you want to go beyond what the typical
> preprocessor does, you pretty much have to write a new
> preprocessor. Lisp's macro facility is out of the box able to easily
> do anything to the input tree that Lisp can do to lists, which is
> quite a lot.
> 
> > That's cool. Unfortunately, Graham's excitement did not carry over to me as
> > the reader. I have some sort of an intuitive idea of a Lisp object as
> > anything enclosed by a "(" and a ")", although I do not beleive that was
> > ever explicity stated in either "On Lisp" or Winston & Horn's book.
> 
> It's surprisingly hard to explain what macros can do and why they are
> different from something like a preprocessor.

Yes it is.  I first got a glimps of the power of Lisp's macro facility
when I hacked together this form inside a macrolet:

(local-form-maker ()
  `(let ((code nil))
     (dolist (form forms (nreverse code))
       (cond ((atom form) (push `(princ ,form) code))
             ((keywordp (first form)) (push `(xxml ,form) code))   
             ((listp (first form)) (push `(xxml ,form) code))   
             ((fboundp (first form)) (push form code))))))

I didn't just have a template.  I built a template computationally at
compile time.

I can't imagine the C preprocessor doing what the loop macro does.

-- 
An ideal world is left as an excercise to the reader.
   --- Paul Graham, On Lisp 8.1
From: Pascal Bourguignon
Subject: Re: Paul Graham's teaching style is bad
Date: 
Message-ID: <87ekmae1ij.fsf@thalassa.informatimago.com>
"Kevin Clancy" <············@hotmail.com> writes:

> On Lisp - 7.1
> "Many languages offer some form of macro, but Lisp macros are singularly
> powerful. When a file of Lisp is compiled, a parser reads the source code
> and sends its output to the compiler. Here's the stroke of genius: the ouput
> of the parser consists of lists of Lisp objects. With macros, we can
> manipulate the program while it's in this intermidiate form between parser
> and compiler."
> 
> Gee. What a revelation. After about a half hour of contemplation, I came to
> the conclusion that what he was trying to say was that you can use Lisp to
> program the preprocessor.
> 
> That's cool. Unfortunately, Graham's excitement did not carry over to me as
> the reader. I have some sort of an intuitive idea of a Lisp object as
> anything enclosed by a "(" and a ")", although I do not beleive that was
> ever explicity stated in either "On Lisp" or Winston & Horn's book.
> 
> So at this point, I'm guessing that the advantage of Lisp macros only comes
> when compilation takes places in the midst of your program... I'm confused.
> 
> What I need is a more detailed explanation. Obviously, since Graham isn't
> telling the reader everything that he knows, can anyone point me to some
> resources that Graham may have used to gain his unrestrainable enthusiasm
> for this language?

Bad teacher?  Change teacher!  

(And remeber that "Bad" in "Bad teacher" is a function of the pupil).

Actually, lisp is not about "(" and ")", but about the fact that the
program is stored as a structure that is manipulable by the program
itself:

+-----------------------------------------------------------------------+
|                                                                       |
| +---+---+   +---+---+   +---+---+   +---+---+                         |
| | * | * |-->| * | * |-->| * | * |-->| * |NIL|                         |
| +---+---+   +---+---+   +---+---+   +---+---+                         |
|   |           |           |           |                               |
|   v           v           v           v                               |
| +-------+   +--------+  +---+---+   +---+---+   +---+---+   +---+---+ |
| | DEFUN |   | SQUARE |  | * |NIL|   | * | * |-->| * | * |-->| * |NIL| |
| +-------+   +--------+  +---+---+   +---+---+   +---+---+   +---+---+ |
|                           |           |           |           |       |
|                           v           v           v           v       |
|                         +---+       +---+       +---+       +---+     |
|                         | N |       | * |       | N |       | N |     |
|                         +---+       +---+       +---+       +---+     |
|                                                                       |
+-----------------------------------------------------------------------+

There are absolutely NO "(" and NO ")" in a lisp program.

-- 
__Pascal Bourguignon__                     http://www.informatimago.com/

Our enemies are innovative and resourceful, and so are we. They never
stop thinking about new ways to harm our country and our people, and
neither do we.