From: ·······@ziplip.com
Subject: Explanation of macros; Haskell macros
Date: 
Message-ID: <GGDUFQOGIAD5H2L3GDEKNREOMFKFLREPEFD3MGCP@ziplip.com>
I think others dropped the ball while trying to explain macros
to non-Lispers recently. The examples I saw posted were either
too difficult or easily doable without macros (maybe even easier).
This probably convinced many Pythonistas that Lispers are
complexity-seeking wackos, and macros are cruft. This only 
applies to some people and *their* macros. Most important, 
all of the examples failed to relate to "the common man" :  
typical python user or programming newbie. As they say,
"if you can't explain it ..."

I intend to correct this. The following example relates to
a problem familiar to all Python users and demonstrates 
two uses of macros: syntax improvement and efficiency gain
through compile-time code introspection.

Let's say you do not have the "for" keyword, but you have
"dolist" for iterating a list and "dotimes" - a simple 
index loop. You want to create "for" just like in Python, and
you also want "for i in range(10000): print i" to be efficient
and avoid constructing the big list (maybe you do not have
enough memory). In Lisp, you can acomplish this with the
following macro:

(defmacro for(i in list &rest rest)
  (if (eql 'in in)
    (if (and (listp list)
             (eql (length list) 2)
             (eql 'range (first list))
             (integerp (second list)))
      `(dotimes (,i ,(second list)) ,@rest)
      `(dolist (,i ,list) ,@rest))
    (error "syntax error")))


You can use it like this:

(for k in (range 10000)
  (print k))

or

(for k in '(666 222 333 111)
  (print "foo")
  (print k))

The macro works by looking at *code* (not values) at 
*compile-time*, and if the right argument is (range xxxx), 
it uses the more efficient "dotimes".

Let me know if the above helped you understand the usefulness
of macros or was just as sucky as the earlier stuff.

BTW, I think Alex made some very good points about 
simplicity and uniformity. I hesitate to say that I agree
with the final verdict, but his reasoning is very sound. 
Lispers who tried to mock him (some outside CLP) just showed 
their own idiocy. This isn't winning Lisp any friends...

Someone pointed out that Haskell has macros. Does anyone
know how they relate to Lisp and Scheme macros? Better, worse,
different? If anyone knows them well, can you show how you 
would do "for i in ...."  using Haskell macros?

From: Terry Reedy
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <FWKdne_wY621sx-iU-KYhA@comcast.com>
<·······@ziplip.com> wrote in message
·············································@ziplip.com...
> enough memory). In Lisp, you can acomplish this with the
> following macro:

I presume this is specifically Common Lisp

[ for i in seq example ]

> Let me know if the above helped you understand the usefulness
> of macros or was just as sucky as the earlier stuff.

Yes, I understood even though I am not familiar with the ` , & and @
prefixes.

Terry J. Reedy
From: Doug Tolton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <c034ovkc79l5lg2idh0fq4kjhpggob1t56@4ax.com>
On Mon, 6 Oct 2003 16:34:12 -0700 (PDT), ·······@ziplip.com wrote:

>I think others dropped the ball while trying to explain macros
>to non-Lispers recently. The examples I saw posted were either
>too difficult or easily doable without macros (maybe even easier).
>This probably convinced many Pythonistas that Lispers are
>complexity-seeking wackos, and macros are cruft. This only 
>applies to some people and *their* macros. Most important, 
>all of the examples failed to relate to "the common man" :  
>typical python user or programming newbie. As they say,
>"if you can't explain it ..."

The problem wasn't that none of the macros weren't good.  The problem
was that any sufficiently complex macro was completely un-intelligible
to a non-lisper.  To the un-initiated the Lisp syntax is dis-orienting
and bewildering.  It does take some time to get use to it,
unfortunately there simply wasn't enough time in that discussion to
convey an adequate level of knowledge for them to understand any
non-trivial macro.
>
>I intend to correct this. The following example relates to
>a problem familiar to all Python users and demonstrates 
>two uses of macros: syntax improvement and efficiency gain
>through compile-time code introspection.
>
>Let's say you do not have the "for" keyword, but you have
>"dolist" for iterating a list and "dotimes" - a simple 
>index loop. You want to create "for" just like in Python, and
>you also want "for i in range(10000): print i" to be efficient
>and avoid constructing the big list (maybe you do not have
>enough memory). In Lisp, you can acomplish this with the
>following macro:
>
>(defmacro for(i in list &rest rest)
>  (if (eql 'in in)
>    (if (and (listp list)
>             (eql (length list) 2)
>             (eql 'range (first list))
>             (integerp (second list)))
>      `(dotimes (,i ,(second list)) ,@rest)
>      `(dolist (,i ,list) ,@rest))
>    (error "syntax error")))
>
>
>You can use it like this:
>
>(for k in (range 10000)
>  (print k))
>
>or
>
>(for k in '(666 222 333 111)
>  (print "foo")
>  (print k))
>
>The macro works by looking at *code* (not values) at 
>*compile-time*, and if the right argument is (range xxxx), 
>it uses the more efficient "dotimes".
>
>Let me know if the above helped you understand the usefulness
>of macros or was just as sucky as the earlier stuff.
>
IIRC this macro was better than some and maybe worse than others.
Again, do you think a Pythonista could understand that macro?  Nope.
For it to be meaningful to them you would have to explain how it works
and what the benefit it is.  Their typical response was "we already
have a for loop"

The other problem is that there is no *singularly* great example of
macros.  It's sort of like saying 5 + 5 is the best example of
addition.  That's not the case, rather it's the ubiquity and utility
of Macros when applied to Lisp as a whole that make them powerful.
Not simply the fact that you can make a "for - in" construct.

>BTW, I think Alex made some very good points about 
>simplicity and uniformity. I hesitate to say that I agree
>with the final verdict, but his reasoning is very sound. 
>Lispers who tried to mock him (some outside CLP) just showed 
>their own idiocy. This isn't winning Lisp any friends...
>
Personally I disagree with this statement. I am assuming you are
talking about Alex Martelli on comp.lang.python.  If this is not who
you mean, disregard the rest.  Alex made some very biased and
prejudiced statements against macros based on a complete
mis-understanding of what they are and how they operate IMO.  We tried
very hard to get him to understand, but many of the statements he
continually made showed a fundamentally flawed understanding of
Macros.  I don't believe I ever mocked him, I was very disgusted with
his attitude, as I am with all attitudes that are based on ignorance.
Does that make him a bad person, or mean that I dislike him? No, I
just don't particularly care for his alarmist attitude.

>Someone pointed out that Haskell has macros. Does anyone
>know how they relate to Lisp and Scheme macros? Better, worse,
>different? If anyone knows them well, can you show how you 
>would do "for i in ...."  using Haskell macros?

I have not personally used Haskell macros, they may be more relevant
to Python in general than Lisp, because Lisp syntax is so dissimilar
from Python.

Ultimately I came away from that discussion with the realization that 
1) macros in Python would never and could never be as powerful as the
Lisp macros, because Lisp Macros are so powerful precisely because of
Lisps syntax for one.
2) even if Macros could some how be implemented in Python, they would
never gain widespread acceptance because too many people mistakenly
believe Macros cause dialectualization and were ultimately responsible
for the death of the Lisp community.

That was a very long, and frustrating discussion.  The amount of
ignorance displayed and the overly alarmist reactions left a bad taste
in my mouth.  This issue is very polarizing because of people's
experience with C style macros.  Unfortunately once an issue becomes a
polarizing topic not much headway can be made with people who believe
the opposite of what you believe.


Doug Tolton
(format t ···@~a~a.~a" "dtolton" "ya" "hoo" "com")
From: Tomasz Zielonka
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <slrnbo44v4.bf9.t.zielonka@zodiac.mimuw.edu.pl>
·······@ziplip.com wrote:
> Someone pointed out that Haskell has macros. Does anyone
> know how they relate to Lisp and Scheme macros? Better, worse,
> different? 

You can find a short comparison of Scheme and Template Haskell (TH) approach
in (pages 12-13):

  http://www.haskell.org/th/papers/meta-haskell.ps

I would say that similarity between them is much bigger than between,
say, TH and C++ template meta-programming, or between Scheme and C++ tmp.

> If anyone knows them well, can you show how you would do "for i in
> ...."  using Haskell macros?

Haskell macros/templates provide mechanisms for introspection. They
allow you to process Haskell abstract syntax trees as values of
algebraic datatype Exp. That's probably a little more complicated than
in LISP and Scheme, because Haskell's syntax is much more complex. 

You could implement "for i in ..." using them, but this would be a bad
example, because as a non-strict (think "lazy") language it will handle
this code gracefully by default.

For example this code prints consecutive positive Integers starting from
1 (if run in the IO monad):

    mapM_ print [1..]

If mapM_ scares you, you can define

    for l f = mapM_ f l

and write it nicely as:
    
    for [1..] print

Besides, Haskell macros aren't applied everywhere by default as in LISP.
You have to ,,splice'' them explicitely (see the paper).

A good example of TH's power is the ability to create a statically
type-checked printf mechanism using format strings like in C. Example:

    $(printf "an int: %d, int in hex: %08x, a string: %20s") 10 255 "foo"

compiles and evaluates to

    "an int: 10, int in hex: 000000ff, a string: foo"

but

    $(printf "an int: %d, int in hex: %08x, a string: %20s") 10 "foo" 255

will raise a compile-time type error.




Recently I have used TH to generate a datatype enumeration all keywords
in some SQL dialect and to create a mapping from strings to these
datatypes. It looks like this:

  keywords :: [String]
  keywords = words
      " ADD ALL ALTER AND ANY AS ASC AUTHORIZATION BACKUP BEGIN BETWEEN \
      [... 160 keywords snipped ...]
      \ VALUES VARYING VIEW WAITFOR WHEN WHERE WHILE WITH WRITETEXT "

  kwConName :: String -> String
  kwConName = id

  -- generates abstract syntax for declaration of Keyword datatype
  dataKeyword :: Dec
  dataKeyword =
      Data
	  []                                              -- context
	  "Keyword"                                       -- datatype name
	  []                                              -- type variables
	  (map (\k -> Constr (kwConName k) []) keywords)  -- constructors
	  (words "Show Eq Ord Enum Bounded")              -- derived instances

  -- generates abstract syntax for a list of pairs like ("SELECT", SELECT)
  -- for all keywords
  keywordMapList :: ExpQ
  keywordMapList =
      foldr
	  (\k l ->
	      let str = return (Lit (String k))
		  con = return (Con (kwConName k))
	      in  [| ($str, $con) : $l |])
	  [| [] |]
	  keywords

Then in another module:

  $(return [dataKeyword])

  keywordMap :: FiniteMap String Keyword
  keywordMap = listToFM $(keywordMapList)

This way I am sure that every keyword is included in the mapping.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
From: ·············@comcast.net
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <llrx7ob8.fsf@comcast.net>
·······@ziplip.com writes:

> I think others dropped the ball while trying to explain macros
> to non-Lispers recently. The examples I saw posted were either
> too difficult or easily doable without macros (maybe even easier).

Macros from production code:

(defmacro debug-message (noise format-string &rest args)
  "Print a message on *DEBUG-IO* using FORMAT-STRING and ARGS
   iff the *DEBUG-NOISE-LEVEL* is equal to or greater than NOISE.

   When writing code, sprinkle calls to DEBUG-MESSAGE at strategic
   points to aid in debugging.  The different noise levels should be
   used at different semantic levels in the code.  Level 0 is
   for only the highest level of functionality, Level 3 is for
   module level, Level 5 is for extreme detail."
  (if (and (boundp '*disable-debug-messages*)
	   (eq *disable-debug-messages* t))
      `(PROGN)
      (let ((noise-var (gensym "NOISE-VAR-")))
	`(LET ((,noise-var ,noise))
	   #+ALLEGRO (DECLARE (:FBOUND FORMAT-DEBUG-MESSAGE))
	   (WHEN-DEBUGGING ,noise-var
	     (FORMAT-DEBUG-MESSAGE ,noise-var ,format-string (LIST ,@args)))))))

This macro lets me write thing like:

  (debug-message 2 "Beginning major phase ~s" *phase*)

at various places in the code.  The amount of debugging noise is
determined by a global variable.  If the variable
*DISABLE-DEBUG-MESSAGES* is bound to 't at compile time, the code is
omitted completely.  This is done when a customer build is created.

(defmacro ignore-errors-unless (condition &body forms)
  "Unless CONDITION evaluates to TRUE, act as IGNORE-ERRORS does while executing FORMS, with the
   the same return values.  If CONDITION evaluates to TRUE, when we don't ignore errors, however
   the return value is as if an IGNORE-ERRORS were around the form.
   Example:  (ignore-errors-unless *debugging* (do stuff) (do more stuff) ...)
             (ignore-errors-unless (eq *debugging* 2) (do stuff) (do more stuff) ...)"
  (let ((block-name (gensym "IGNORE-ERRORS-UNLESS-BLOCK-"))
        (cond-value (gensym "IGNORE-ERRORS-UNLESS-COND-VALUE-")))
    ;; Evaluate the cond value before the body for less confusing semantics.
    ;; (We don't want the block established around the conditional).
    `(LET ((,cond-value ,condition))
       (BLOCK ,block-name
         (HANDLER-BIND (#+allegro (EXCL:INTERRUPT-SIGNAL #'SIGNAL)

                                  (CL:ERROR (FUNCTION
                                             (LAMBDA (CONDITION)
                                               #+ALLEGRO (DECLARE (:FBOUND DEBUG-NOTE-CONDITION))
                                               (UNLESS ,cond-value
                                                 (DEBUG-NOTE-CONDITION "caught by an ignore-errors-unless form" CONDITION)
                                                 (RETURN-FROM ,block-name
                                                              (values NIL CONDITION)))))))
                               (VALUES (LOCALLY ,@forms) NIL))))))

As you might imagine, this one discards errors unless some
condition is true.

(defmacro ignore-errors-unless-debugging (&rest body)
  "Just like IGNORE-ERRORS, except that if *debug-noise-level* is non-nil,
   errors are not ignored."
  `(IGNORE-ERRORS-UNLESS (AND *DEBUG-NOISE-LEVEL*
                              (NULL *IGNORE-ERRORS-EVEN-IF-DEBUGGING*))
     ,@body))

Very handy when debugging a server.  When serving web requests, you don't
want errors to take down the entire server.  Yet when you are debugging
it, you don't want to suppress them.  Of course, when you are running
test regressions during debugging, you *do* want to suppress them....

 
Occasionally I have to move large amounts of data very fast.  There
are common-lisp functions for doing this, but sometimes you need to go
flat out as fast as possible.  This generally requires adding a lot of
declarations.  But a function that is declared to operate solely on,
say, 1-byte wide vectors looks amazingly like one that operates on
2-byte wide vectors, except for the declarations.  Hence the macro:

(define-fast-subvector-mover %simple-subvector-8b-move  simple-array (unsigned-byte 8))

which expands into:

(PROGN
  (DECLAIM (FTYPE
            #'((SIMPLE-ARRAY (UNSIGNED-BYTE 8) (*)) (INTEGER 0 (8388608)) (INTEGER 0 (8388608)) (SIMPLE-ARRAY (UNSIGNED-BYTE 8) (*)) (INTEGER 0 (8388608)))
            %SIMPLE-SUBVECTOR-8B-MOVE-LEFT
            %SIMPLE-SUBVECTOR-8B-MOVE-RIGHT))
  (DEFUN %SIMPLE-SUBVECTOR-8B-MOVE-LEFT (SOURCE SRC-START SRC-LIMIT DEST DEST-START)
    (DECLARE (TYPE (SIMPLE-ARRAY (UNSIGNED-BYTE 8) (*)) SOURCE)
             (TYPE (SIMPLE-ARRAY (UNSIGNED-BYTE 8) (*)) DEST)
             (TYPE (INTEGER 0 (8388608)) SRC-START SRC-LIMIT DEST-START)
             (OPTIMIZE
              (COMPILATION-SPEED 0)
              (DEBUG 0)
              (SAFETY 0)
              (SPACE 0)
              (SPEED 3)))
    (PROGN
      (LOOP
        (PROGN
          (WHEN (= SRC-START SRC-LIMIT) (RETURN-FROM NIL NIL))
          (SETF (AREF DEST DEST-START) (AREF SOURCE SRC-START))
          (INCF SRC-START)
          (INCF DEST-START)))))
  (DEFUN %SIMPLE-SUBVECTOR-8B-MOVE-RIGHT (SOURCE SRC-START SRC-LIMIT DEST DEST-START)
    (DECLARE (TYPE (SIMPLE-ARRAY (UNSIGNED-BYTE 8) (*)) SOURCE)
             (TYPE (SIMPLE-ARRAY (UNSIGNED-BYTE 8) (*)) DEST)
             (TYPE (INTEGER 0 (8388608)) SRC-START SRC-LIMIT DEST-START)
             (OPTIMIZE
              (COMPILATION-SPEED 0)
              (DEBUG 0)
              (SAFETY 0)
              (SPACE 0)
              (SPEED 3)))
    (PROGN
      (PROGN
        (INCF DEST-START (- SRC-LIMIT SRC-START))
        (LOOP
          (WHEN (= SRC-LIMIT SRC-START) (RETURN-FROM NIL NIL))
          (DECF SRC-LIMIT)
          (DECF DEST-START)
          (SETF (AREF DEST DEST-START) (AREF SOURCE SRC-LIMIT)))))))

A decent lisp compiler can compile this into *very* tight code.
But even better is the fact that if you need to move 2-byte arrays
around, you don't have to write anything more than:

(define-fast-subvector-mover %simple-subvector-16b-move  simple-array (unsigned-byte 16))


Let us suppose that we have a function that takes function
as an argument.  For instance,

(defun my-mapc (func list)
  (dolist (element list)
    (funcall func element)))

Now this works, but in performance critical code it may
be a bottleneck (closure creation and funcalling).
It'd be nice if the compiler knew how to handle this specially.

This following function is a parser for literal lambda expressions:

(defun destructure-function-lambda (arity fl receiver if-not-function)
  "If fl is of the form (FUNCTION (LAMBDA (bound-variable-list) docstring decls body))
   invoke receiver on the bound-variable-list, docstring, decls, and the body.

   If fl is of the form (FUNCTION name), invoke receiver on a
   fake eta-expanded form.

   If fl is of the form NAME, invoke receiver on a
   fake eta-expanded form.

   Otherwise invoke if-not-function."
  (macrolet ((list-length-equals-one (list)
               `(AND (CONSP ,list)
                     (NULL (CDR ,list))))

             (list-length-greater-than-one (list)
               `(AND (CONSP ,list)
                     (CONSP (CDR ,list))))

             (is-function-form (form)
               `(AND (CONSP ,form)
                     (EQ (CAR ,form) 'FUNCTION)
                     (LIST-LENGTH-EQUALS-ONE (CDR ,form))))

             (function-form-body (function-form)
               `(CADR ,function-form))

             (is-lambda-form (form)
               `(AND (CONSP ,form)
                     (EQ (CAR ,form) 'LAMBDA)
                     (LIST-LENGTH-GREATER-THAN-ONE (CDR ,form))))

             (lambda-form-arguments (lambda-form)
               `(CADR ,lambda-form))

             (lambda-form-body (lambda-form)
               `(CDDR ,lambda-form)))

    (cond ((is-function-form fl)
           (let ((pl (function-form-body fl)))
             ;; Look for `(LAMBDA ...)
             (cond ((is-lambda-form pl)
                    (multiple-value-bind (docstring declarations body)
                        (split-declarations (lambda-form-body pl))
                      (funcall receiver (lambda-form-arguments pl) docstring declarations body)))

                   ;; can't fake eta expand if arity is unknown
                   ((null arity) (funcall if-not-function))

                   ((symbolp pl)                ; is something like (function foo)
                    ;; perform eta expansion
                    (let ((arglist nil))
                      (dotimes (i arity)
                        (push (gensym "ARG-") arglist))
                      (funcall receiver arglist nil nil `((,pl ,@arglist)))))

                   (t (funcall if-not-function)))))

          ;; Look for naked '(lambda ...)
          ;; treat as if it were '(function (lambda ...))
          ((is-lambda-form fl)
           (multiple-value-bind (docstring declarations body)
               (split-declarations (lambda-form-body fl))
             (funcall receiver (lambda-form-arguments fl) docstring declarations body)))

          ;; Can't fake an eta expansion if we don't know the arity.
          ((null arity) (funcall if-not-function))

          ;; Perform an ETA expansion
          ((symbolp fl)
           (let ((arglist nil))
             (dotimes (i arity)
               (push (gensym "ARG-") arglist))
             (funcall receiver arglist nil nil `((FUNCALL ,fl ,@arglist)))))

          (t (funcall if-not-function)))))

Now we can use it as follows:

(defmacro my-mapc (func list)
  (destructure-function-lambda 1 func
    (lambda (bvl docstr decls body)
      (declare (ignore docstr))
      `(DOLIST (,(car bvl) ,list)
         ,@decls
         ,@body))
    (lambda ()
      (error "~s cannot be destructured." func))))


And here is the result:

(macroexpand-1 '(my-mapc #'(lambda (x) (+ x 2)) some-list))
  =>  (DOLIST (X SOME-LIST) (+ X 2))

(macroexpand-1 '(my-mapc (lambda (x) (+ x 2)) some-list))
  =>  (DOLIST (X SOME-LIST) (+ X 2))

(macroexpand-1 '(my-mapc #'print some-list))
  =>  (DOLIST (#:ARG-9909 SOME-LIST) (PRINT #:ARG-9909))



When I want to emit a web page with an applet on it,
there is a ton of boilerplate that has to go out.  But the
boilerplate is parameterized, so you can't just write a text
file and be done with it.  This macro abstracts that away:

(defmacro html-with-applet (req &body body)
  (with-unique-names (command ticket comment success-page fail-page)
   `(PROGN
      (EMIT-HTML-HEADER (NET.ASERVE:REQUEST-REPLY-STREAM ,req))
      (MACROLET ((EMBED-APPLET (,COMMAND ,TICKET ,COMMENT ,SUCCESS-PAGE ,FAIL-PAGE)
       `(NET.ASERVE::HTML
         ((:div :id "applet-container")
          (:P ,,comment)
          ((:object 
            :code "Applet.class"
            :id "applet"
            :width  "100%"
            :height "300"
            :standby "Loading applet...")
           ((:param :name "URL"
                    :value (render-uri (extend-uri-query
                                        (net.aserve:request-uri req)
                                        '(:absolute "applet-callback.htm")
                                        `((:command . ,',,command)
                                          (:ticket . ,,,ticket)))
                                       nil)))
           ((:param name "SUCCESSURL" value (render-uri
                                             (extend-uri-query 
                                              (net.aserve:request-uri req)
                                              `(:absolute ,',,success-page)
                                              `((:ticket . ,,,ticket)))
                                             nil)))
           ((:param name "FAILURL"    value (render-uri
                                             (extend-uri-query 
                                              (net.aserve:request-uri req)
                                              `(:absolute ,',,fail-page)
                                              `((:ticket . ,,,ticket)))
                                             nil))))))))
        (NET.ASERVE::HTML ,@body))
      (EMIT-HTML-TRAILER (NET.ASERVE:REQUEST-REPLY-STREAM ,req)))))

This macro writes a macro with backquoted list structure in it.
The user of this macro simply writes:

     (embed-applet :file-browser
                  ticket
                  "Select a file."
                  "file-selected.htm"
                  "cancel.htm")

Within the template.

I don't think these are too complicated to understand, and 
although some of them could be handled by functions and such,
they pretty much capture *exactly* what I want write.  You don't
need to understand `idioms' and `patterns' to know to
embed an applet.
From: Kenny Tilton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <24rgb.20813$pv6.3619@twister.nyc.rr.com>
·······@ziplip.com wrote:
> I think others dropped the ball while trying to explain macros
> to non-Lispers recently. 

...<snip>

> Let's say you do not have the "for" keyword, but you have
> "dolist" for iterating a list and "dotimes" - a simple 
> index loop. You want to create "for" just like in Python, 

Wow, talk about dropping the ball. Translation: "You should learn Lisp 
because it has macros so you can recreate Python in Lisp and not learn 
Lisp."

If you want to be an educator, you gotta motivate your students. Your 
macro was fine in all regards except that its motivation ("avoid Lisp by 
learning advanced Lisp!") is, um, unconvincing.

kenny
From: Rolf Wester
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bltq94$mo8$1@nets3.rz.RWTH-Aachen.DE>
·······@ziplip.com wrote:
> Let's say you do not have the "for" keyword, but you have
> "dolist" for iterating a list and "dotimes" - a simple 
> index loop. You want to create "for" just like in Python, and
> you also want "for i in range(10000): print i" to be efficient
> and avoid constructing the big list (maybe you do not have
> enough memory). In Lisp, you can acomplish this with the
> following macro:
> 
> (defmacro for(i in list &rest rest)
>   (if (eql 'in in)
>     (if (and (listp list)
>              (eql (length list) 2)
>              (eql 'range (first list))
>              (integerp (second list)))
>       `(dotimes (,i ,(second list)) ,@rest)
>       `(dolist (,i ,list) ,@rest))
>     (error "syntax error")))
> 
> 
What will a Pythonista think about Lisp macros when he/she tries:

(defun f (n)
   (for i in (range n)
        (print i)))
(f 10000)

Maybe the macro should better be written:

(defmacro for (i in list &rest rest)
   (if (eql 'in in)
     (if (and (listp list)
              (eql (length list) 2)
              (eql 'range (first list))
              (or (integerp (second list)) (symbolp (second list))))
       `(if (integerp ,(second list))
		   (dotimes (,i ,(second list)) ,@rest)
		   (error "not an integer"))
       `(dolist (,i ,list) ,@rest))
     (error "syntax error")))


Rolf Wester
From: Robert Klemme
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bltubn$ga56e$2@ID-52924.news.uni-berlin.de>
<·······@ziplip.com> schrieb im Newsbeitrag
·············································@ziplip.com...
> I think others dropped the ball while trying to explain macros
> to non-Lispers recently. The examples I saw posted were either
> too difficult or easily doable without macros (maybe even easier).
> This probably convinced many Pythonistas that Lispers are
> complexity-seeking wackos, and macros are cruft. This only
> applies to some people and *their* macros. Most important,
> all of the examples failed to relate to "the common man" :
> typical python user or programming newbie. As they say,
> "if you can't explain it ..."
>
> I intend to correct this. The following example relates to
> a problem familiar to all Python users and demonstrates
> two uses of macros: syntax improvement and efficiency gain
> through compile-time code introspection.
>
> Let's say you do not have the "for" keyword, but you have
> "dolist" for iterating a list and "dotimes" - a simple
> index loop. You want to create "for" just like in Python, and
> you also want "for i in range(10000): print i" to be efficient
> and avoid constructing the big list (maybe you do not have
> enough memory). In Lisp, you can acomplish this with the
> following macro:
>
> (defmacro for(i in list &rest rest)
>   (if (eql 'in in)
>     (if (and (listp list)
>              (eql (length list) 2)
>              (eql 'range (first list))
>              (integerp (second list)))
>       `(dotimes (,i ,(second list)) ,@rest)
>       `(dolist (,i ,list) ,@rest))
>     (error "syntax error")))
>
>
> You can use it like this:
>
> (for k in (range 10000)
>   (print k))
>
> or
>
> (for k in '(666 222 333 111)
>   (print "foo")
>   (print k))
>
> The macro works by looking at *code* (not values) at
> *compile-time*, and if the right argument is (range xxxx),
> it uses the more efficient "dotimes".
>
> Let me know if the above helped you understand the usefulness
> of macros or was just as sucky as the earlier stuff.

I am your target audience (i.e. Lisp newby, although not coming from
Python).  And I was missing the meaning of "`" and "," in the explanation
of the macro definition.  This is what I figured:

"`" quotes an expression that is not evaluated but taken as is (in this
case returned).
"," undoes the effect of "`", i.e. evaluates the expression in place, kind
of template replacement.

Let me know if the above was correct.

Kind regards

    robert


FUP set to c.l.l
From: Lars Brinkhoff
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <858ynxmm9l.fsf@junk.nocrew.org>
"Robert Klemme" <········@gmx.net> writes:
> I was missing the meaning of "`" and "," in the explanation of the
> macro definition.  This is what I figured:
> 
> "`" quotes an expression that is not evaluated but taken as is (in this
> case returned).
> "," undoes the effect of "`", i.e. evaluates the expression in place, kind
> of template replacement.
> 
> Let me know if the above was correct.

You've got the right idea.  Experiment with this:

  (let ((x 2)
        (y '(4 5 6)))
    `(1 ,x 3 ,@y 7))

-- 
Lars Brinkhoff,         Services for Unix, Linux, GCC, HTTP
Brinkhoff Consulting    http://www.brinkhoff.se/
From: Robert Klemme
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <blu2a5$g4pm2$1@ID-52924.news.uni-berlin.de>
"Lars Brinkhoff" <·········@nocrew.org> schrieb im Newsbeitrag
···················@junk.nocrew.org...
> "Robert Klemme" <········@gmx.net> writes:
> > I was missing the meaning of "`" and "," in the explanation of the
> > macro definition.  This is what I figured:
> >
> > "`" quotes an expression that is not evaluated but taken as is (in
this
> > case returned).
> > "," undoes the effect of "`", i.e. evaluates the expression in place,
kind
> > of template replacement.
> >
> > Let me know if the above was correct.
>
> You've got the right idea.  Experiment with this:
>
>   (let ((x 2)
>         (y '(4 5 6)))
>     `(1 ,x 3 ,@y 7))

I see.  And ",@" inserts the elements of the list into the current list
instead the whole list.
Your expression yields: (1 2 3 4 5 6 7)

(let ((x 2)
        (y '(4 5 6)))
    `(1 ,x 3 ,y 7))

Yields (1 2 3 (4 5 6) 7) as expected.

Thanks!

    robert
From: Coby Beck
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bm0n35$28un$1@otis.netspace.net.au>
<·······@ziplip.com> wrote in message
·············································@ziplip.com...
> I think others dropped the ball while trying to explain macros
> to non-Lispers recently. The examples I saw posted were either
> too difficult or easily doable without macros (maybe even easier).

Here's a nice example from some production code I wrote that is easy to
grok.

The purpose: a socket server excepts a set of specific commands from
clients.  Client commands must be verified as allowed and the arguments
marshalled before applying the appropriate function to the arguments.  I
wanted a clean way to express this and automate the writing of error
catching code.

Usage: define-server-cmd name (method-parameters) constraints code

Sample usage:
(define-server-cmd set-field-sequence ((session morph-configuration-session)
field-list)
    ((listp field-list)
     (remove-if-not #'(lambda (key) (member key *logical-types*))
field-list))
  (with-slots (client source-blueprint state) session
    (setf (field-sequence (source-blueprint session)) field-list)
    (setf state :blueprint-set)
    (send session (write-to-string state))))

The resulting expansion:
(PROGN
  (DEFMETHOD SET-FIELD-SEQUENCE
    ((SESSION MORPH-CONFIGURATION-SESSION) FIELD-LIST)
    (WITH-SLOTS (CLIENT SOURCE-BLUEPRINT STATE)
                SESSION
      (SETF (FIELD-SEQUENCE (SOURCE-BLUEPRINT SESSION))
            FIELD-LIST)
      (SETF STATE :BLUEPRINT-SET)
      (SEND SESSION (WRITE-TO-STRING STATE))))
  (DEFMETHOD MARSHAL-ARGS-FOR-CMD
    ((CMD (EQL 'SET-FIELD-SEQUENCE))
     (SESSION MORPH-CONFIGURATION-SESSION))
    (LET (FIELD-LIST)
      (PROGN
        (SETF FIELD-LIST
              (RECEIVE SESSION :TIMEOUT *COMMAND-PARAMETER-TIMEOUT*))
        (UNLESS FIELD-LIST
          (ERROR 'TIMEOUT-ERROR
                 :EXPECTATION
                 (FORMAT NIL "~A parameter to ~A command" 'FIELD-LIST CMD)
                 :TIMEOUT
                 *COMMAND-PARAMETER-TIMEOUT*)))
      (UNLESS (LISTP FIELD-LIST)
        (ERROR 'COMMAND-CONSTRAINT-VIOLATION
               :CONSTRAINT
               '(LISTP FIELD-LIST)
               :COMMAND
               CMD))
      (UNLESS (REMOVE-IF-NOT #'(LAMBDA (KEY)
                                 (MEMBER KEY *LOGICAL-TYPES*))
                             FIELD-LIST)
        (ERROR 'COMMAND-CONSTRAINT-VIOLATION
               :CONSTRAINT
               '(REMOVE-IF-NOT #'(LAMBDA (KEY)
                                   (MEMBER KEY *LOGICAL-TYPES*))
                               FIELD-LIST)
               :COMMAND
               CMD))
      (LIST FIELD-LIST)))
  (PUSHNEW 'SET-FIELD-SEQUENCE *CONFIG-SERVER-COMMANDS*))

Usage of what the macro gave me in context (some error handling noise
removed):

(defmethod run-config-command-loop ((session morph-configuration-session))
  (let ((*package* (find-package :udt)))
  (unwind-protect
      (with-slots (client) session
        (loop
         (let (cmd)
           (setf cmd (receive session :timeout *command-timeout* :eof-value
:eof))
               (cond
                ((or (eq cmd :eof) (eq cmd :stop)) (return))
                ((member cmd *config-server-commands*)
                 (let ((cmd-args (marshal-args-for-cmd cmd session)))
                   (apply cmd session cmd-args)))
                (t (execute-generic-command cmd client)))))

        (send session "session loop terminated"))
    (when (eq (state session) :finalized)
        (setf *active-sessions* (delete session *active-sessions*))))))

The macro definition:

(defmacro define-server-cmd (name (session-specializer &rest args)
     constraints &body body)
  (let ((session-var (car session-specializer))
        (session-class (cadr session-specializer)))
    `(progn
       (defmethod ,name ((,session-var ,session-class)
          ,@(mapcar #'(lambda (arg)
   (if (symbolp arg) arg (car arg)))
      args))
  ,@body)
       (defmethod marshal-args-for-cmd
           ((cmd (eql ',name)) ,session-specializer)
         (let (,@args)
           ,@(loop for var in args
                   collect
     `(progn
        (setf ,var (receive ,session-var
       :timeout *command-parameter-timeout*))
        (unless ,var
   (error 'timeout-error
          :expectation (format nil "~A parameter to ~A command"
                               ',var cmd)
          :timeout *command-parameter-timeout*))))
           ,@(loop for con in constraints
                   collect
     `(unless ,con
        (error 'command-constraint-violation
        :constraint ',con
        :command cmd)))
           (list ,@args)))
       (pushnew ',name *config-server-commands*))))

I think the advantages are tremendously obvious, and very satisfying to take
advantage of!

-- 
Coby Beck
(remove #\Space "coby 101 @ big pond . com")
From: Lex Spoon
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3wuau4owd.fsf@logrus.dnsalias.net>
This thread has seemed to miss the biggest advantage of macros.  Most
examples so far are cases where the macro buys you faster code.  This
is not extremely exciting, IMHO, because a better compiler can often
accomplish the things that are described.  If you care that much about
performance then surely you want to be using a good optimizing
compiler, and a good compiler will surely know about, e.g., for loops
that go across constant ranges.  I tend to think of macros as bad
style for this kind of thing, unless it's very clearly a performance
problem you are having.  Macros often look like functions, but they
don't act like them, and it's very easy to introduce bugs with them.

A much bigger advantage of macros is that you can literally extend
the language.  For example, it is nice to be able to type something
like this:

     (regex (| h H)  "ello, "  (| w W)  orld  (? "!"))


To allow this in the nicest way requires using a macro for 'regex.
Without macros, you can still do it:

     (regex '(| h H)  "ello, "  (| w W)  orld  (? "!"))

but now this guy is going to get compiled at runtime, and you get into
the issue of trying to save the compiled regex somewhere ahead of
time.  And while regexes themselves compile pretty quickly, suppose
it's something more like:

     (parser
          (grammer
             ;;... a BNF grammer ...



I also loved the example of both printing a statement and executing
it, which is extremely useful for assertion checking.  You can't
really do this properly without macros.



-Lex
From: Robert Klemme
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bniugm$11k620$1@ID-52924.news.uni-berlin.de>
"Lex Spoon" <···@cc.gatech.edu> schrieb im Newsbeitrag
···················@logrus.dnsalias.net...
> This thread has seemed to miss the biggest advantage of macros.  Most
> examples so far are cases where the macro buys you faster code.  This
> is not extremely exciting, IMHO, because a better compiler can often
> accomplish the things that are described.  If you care that much about
> performance then surely you want to be using a good optimizing
> compiler, and a good compiler will surely know about, e.g., for loops
> that go across constant ranges.  I tend to think of macros as bad
> style for this kind of thing, unless it's very clearly a performance
> problem you are having.  Macros often look like functions, but they
> don't act like them, and it's very easy to introduce bugs with them.
>
> A much bigger advantage of macros is that you can literally extend
> the language.  For example, it is nice to be able to type something
> like this:
>
>      (regex (| h H)  "ello, "  (| w W)  orld  (? "!"))
>
>
> To allow this in the nicest way requires using a macro for 'regex.
> Without macros, you can still do it:
>
>      (regex '(| h H)  "ello, "  (| w W)  orld  (? "!"))
>
> but now this guy is going to get compiled at runtime, and you get into
> the issue of trying to save the compiled regex somewhere ahead of
> time.  And while regexes themselves compile pretty quickly, suppose
> it's something more like:
>
>      (parser
>           (grammer
>              ;;... a BNF grammer ...
>
>
>
> I also loved the example of both printing a statement and executing
> it, which is extremely useful for assertion checking.  You can't
> really do this properly without macros.

Just for the sake of my understanding: could one summarize this as "macros
make control of *when* something is evaluated easier"?  I mean, marco
arguments are not evaluated before the macro "call" as opposed to function
arguments.  With that, you can decide inside the macro, how you treat
those arguments and if you evaluate them at all.  Thx!

Regards

    robert
From: Alain Picard
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <87brs2tjut.fsf@memetrics.com>
"Robert Klemme" <········@gmx.net> writes:

> Just for the sake of my understanding: could one summarize this as "macros
> make control of *when* something is evaluated easier"?  

More precisely: "macros make control of when, if, and how often,
                 something is evaluated _possible_."  

Functions (your only other option) give you no choice.

But, yeah, you've got it.

-- 
It would be difficult to construe        Larry Wall, in  article
this as a feature.			 <·····················@netlabs.com>
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnpscv$9dv$1@news.oberberg.net>
Alain Picard wrote:

> "Robert Klemme" <········@gmx.net> writes:
> 
>>Just for the sake of my understanding: could one summarize this as "macros
>>make control of *when* something is evaluated easier"?  
> 
> More precisely: "macros make control of when, if, and how often,
>                  something is evaluated _possible_."  
> 
> Functions (your only other option) give you no choice.

This statement is wrong if left in full generality: higher-order 
functions can control quite precisely what gets evaluated when. If the 
language offers both lazy and strict parameters, evaluation time control 
extends to the parameter expressions as well.
It's a different kind of control than macros, of course. (It would be 
interesting to see how things would map from macros to functions and 
vice versa.)

Regards,
Jo
From: Lex Spoon
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3he1qgvyj.fsf@logrus.dnsalias.net>
Joachim Durchholz <·················@web.de> writes:
> This statement is wrong if left in full generality: higher-order
> functions can control quite precisely what gets evaluated when. 

They don't let you execute stuff at compile time.  If you write down:

     (parser '(    ;; ...  10 pages of BNF ... ;;
       ))


Then the parser is going to be computed at runtime.  HOF themselves
don't help you compute stuff at compile time.  (Though one can
certainly imagine a language where compile-time execution is
controlled by pragmas.)


-Lex
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnv8rd$npk$1@news.oberberg.net>
Lex Spoon wrote:

> Joachim Durchholz <·················@web.de> writes:
> 
>>This statement is wrong if left in full generality: higher-order
>>functions can control quite precisely what gets evaluated when. 
> 
> They don't let you execute stuff at compile time.

Ah, I didn't think of compile-time evaluation, I was thinking about 
evaluation stuff sooner or later at run-time.

And, of course, macros can evaluate at compile time.
Personally, I'd prefer to do compile-time evaluation based on "the 
compiler will evaluate all known-to-be-constant expressions". The 
advantage here is that programmers don't need to learn another 
sublanguage for compile-time expressions.

I haven't seen this done in full generality though, so I don't know how 
well this would work in practice.

Regards,
Jo
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3n0bglh9i.fsf@javamonkey.com>
Joachim Durchholz <·················@web.de> writes:

> And, of course, macros can evaluate at compile time. Personally, I'd
> prefer to do compile-time evaluation based on "the compiler will
> evaluate all known-to-be-constant expressions". The advantage here
> is that programmers don't need to learn another sublanguage for
> compile-time expressions.

Ah, but in Lisp we don't have to. We use Lisp.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo0823$5ue$1@news.oberberg.net>
Peter Seibel wrote:

> Joachim Durchholz <·················@web.de> writes:
> 
>>And, of course, macros can evaluate at compile time. Personally, I'd
>>prefer to do compile-time evaluation based on "the compiler will
>>evaluate all known-to-be-constant expressions". The advantage here
>>is that programmers don't need to learn another sublanguage for
>>compile-time expressions.
> 
> Ah, but in Lisp we don't have to. We use Lisp.

Having readers and special forms /is/ an extra sublanguage. I don't have 
to learn extra syntax for these forms (which is good), but I do have to 
learn about a lot of special rules that apply to macros and nothing else 
(which is not so good).

Letting the compiler evaluate what it can means that I don't even have 
to learn extra forms.

Actually, that's one of the reasons that keeps my from trying out a 
modern Lisp: I'd have to learn all these extra forms, and I've got a 
feeling that macrology � la Lisp is oversophisticated for something as 
simple as compile-time evaluation.

I'm pretty sure that macros solve more problems than just compile-time 
evaluation. I just suspect that better solutions are available in every 
case, and I not just suspect but know that macros have some very serious 
disadvantages (such as bad debugger interaction, a potential for really 
ugly hairballs, and a constant temptation for stopgap solutions that 
"work well enough").
Lisp-the-language is a quite pretty lean-and-mean KISS language. The 
stuff that's built on top of it (macros, readers, dispatch mechanisms, 
etc. etc.) is neither lean nor KISS nor (IMHO) pretty - YMMV. Or, more 
to the point: I have yet to see something that cannot be done in a 
leaner, more KISS way.
Which is why I'm going to stick with functional languages. After all, 
the higher-order stuff was what attracted me to Lisp in the first place, 
the rest of the language less than impressed me. I'll grant that modern 
Lisps have found ways around any problems (otherwise, modern Lisps 
wouldn't be in use), but why mess with workarounds if I can have the 
cake (higher-order programming) and eat it, too (amenability to static 
analysis)?

Regards,
Jo
From: Kenny Tilton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <oySob.29283$Gq.7951352@twister.nyc.rr.com>
Joachim Durchholz wrote:
> Lisp-the-language is a quite pretty lean-and-mean KISS language. The 
> stuff that's built on top of it (macros, readers, dispatch mechanisms, 
> etc. etc.) is neither lean nor KISS

Do what I did (well, not /you/, but someone else might): don't use fun 
stuff until you are ready for it. Took me a couple of weeks before I 
started writing macros, longer before I used the MOP, longer still 
before nifty use of special variables and then symbol macros. etc etc. 
The thing is, as a developer of serious applications, I appreciate and 
make good use of just about everything in CL.

I would so totally not like to have to reinvent all that stuff myself 
--I have applications to write!-- or end up with a kenny-specific 
environment so no one else could ever run my code.

Gotta go do my first read macro...

:)

kenny

-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3brrwklzh.fsf@javamonkey.com>
Joachim Durchholz <·················@web.de> writes:

> Peter Seibel wrote:
> 
> > Joachim Durchholz <·················@web.de> writes:
> >
> >>And, of course, macros can evaluate at compile time. Personally, I'd
> >>prefer to do compile-time evaluation based on "the compiler will
> >>evaluate all known-to-be-constant expressions". The advantage here
> >>is that programmers don't need to learn another sublanguage for
> >>compile-time expressions.
> > Ah, but in Lisp we don't have to. We use Lisp.
> 
> Having readers and special forms /is/ an extra sublanguage. I don't
> have to learn extra syntax for these forms (which is good), but I do
> have to learn about a lot of special rules that apply to macros and
> nothing else (which is not so good).

Hmmmm. The special forms (25 of them, called special operators these
days, by the by) are used the same in macros and functions. Lisp's
customizable reader is a separate thing--there is no need to customize
the reader to write macros.

> Letting the compiler evaluate what it can means that I don't even
> have to learn extra forms.

I'm not sure what "extra" forms you're talking about. Other than
DEFMACRO, I guess. But by that argument we'd be better off without
DEFUN too because that's just another darn thing to learn.
> 
> Actually, that's one of the reasons that keeps my from trying out a
> modern Lisp: I'd have to learn all these extra forms, and I've got a
> feeling that macrology � la Lisp is oversophisticated for something
> as simple as compile-time evaluation.

Yes, it probably would be over kill if that was all it was for.

> I'm pretty sure that macros solve more problems than just
> compile-time evaluation.

Yup.

> I just suspect that better solutions are available in every case,

Interesting. A lot of people suspect that who haven't actually used
Common Lisp macros. Yet almost all Common Lispers--who by in large are
*not* monolinguists--think macros are one of Common Lisp's great
features. I'm not saying your wrong, but if those better solutions are
out there for all the things I can do with macros, I haven't seen
them. Now I don't know Haskell or ML so I'm also suffering from finite
knowledge. Maybe one day I'll have time to learn one of them for
myself and see if they really do offer better solutions.

> and I not just suspect but know that macros have some very serious
> disadvantages (such as bad debugger interaction, a potential for
> really ugly hairballs, and a constant temptation for stopgap
> solutions that "work well enough").

Well, of those the debugger interaction is perhaps the most serious.
Yet in practice (Hey Pascal, I almost said "in 99% of cases"!) it
doesn't seem to be that much of a problem. Maybe that's because we've
just learned to deal with the pain; maybe MACROEXPAND is all you
really need to get your bearings. At any rate, there's no in principle
that a Lisp implementation couldn't keep track of macro information
along with the compiled code just the way most compiler keep track of
line number information in order to show you the code as written in
the debugger. (And if it was really slick to let you step through the
macro expansion, etc.)

> Lisp-the-language is a quite pretty lean-and-mean KISS language. The
> stuff that's built on top of it (macros, readers, dispatch
> mechanisms, etc. etc.) is neither lean nor KISS nor (IMHO) pretty -
> YMMV.

Clearly. I find Common Lisp to be a pretty beautiful piece of
*engineering*. Which may be different than a beautiful realization of
a beautiful theory.

> Or, more to the point: I have yet to see something that cannot be
> done in a leaner, more KISS way.

Well, if I promise to continue to think that someday I really should
learn a hard-core FP language so I can see what all the static typing
fuss is about, will you promise to think in the back of your mind that
maybe someday you should learn Common Lisp and see what makes us all
so gaga over macros.

> Which is why I'm going to stick with functional languages. After
> all, the higher-order stuff was what attracted me to Lisp in the
> first place, the rest of the language less than impressed me. I'll
> grant that modern Lisps have found ways around any problems
> (otherwise, modern Lisps wouldn't be in use), but why mess with
> workarounds if I can have the cake (higher-order programming) and
> eat it, too (amenability to static analysis)?

Right on. If that's the flavor of cake--enjoy it.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Jesse Tov
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <slrnbq88ua.ivk.tov@tov.student.harvard.edu>
Peter Seibel <·····@javamonkey.com>:
> them. Now I don't know Haskell or ML so I'm also suffering from finite
> knowledge. Maybe one day I'll have time to learn one of them for
> myself and see if they really do offer better solutions.

The existence of Template Haskell indicates to me that there are things
people want to do with macros that aren't reasonably done in Haskell.  I
don't even know if I've ever wanted to do these things, because people
rarely miss language features that they don't know.

Jesse
-- 
"A hungry man is not a free man."      --Adlai Stevenson
From: Kenny Tilton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <COZob.29502$Gq.8134729@twister.nyc.rr.com>
Jesse Tov wrote:
> Peter Seibel <·····@javamonkey.com>:
> 
>>them. Now I don't know Haskell or ML so I'm also suffering from finite
>>knowledge. Maybe one day I'll have time to learn one of them for
>>myself and see if they really do offer better solutions.
> 
> 
> The existence of Template Haskell indicates to me that there are things
> people want to do with macros that aren't reasonably done in Haskell.  I
> don't even know if I've ever wanted to do these things, because people
> rarely miss language features that they don't know.

A language feature is not worth having unless it meets a need which 
exists independent of anyone thinking to create said language feature. 
If you follow links below and poke around the Cliki you can locate those 
folks who got to Lisp via the Greenspun route in some way shape or form, 
people who were trying to do Lisp, not knowing there was such a thing.

I once had a contract to develop a browser app that was going to have 
about twenty screens. They would all work the same, but on different 
views of the DB. COBOL does not have macros, but I sure as hell wasn't 
going to write one and clone it eighteen times.

COBOL /does/ have COPY REPLACING. They may not have intended for someone 
to copy an entire program splicing in different form names and RDB view 
names, but where there is a lazy programmer...

:)

kenny


> 
> Jesse

-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Jesse Tov
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <slrnbqbafl.ea6.tov@tov.student.harvard.edu>
Kenny Tilton <·······@nyc.rr.com>:
> Jesse Tov wrote:
>> The existence of Template Haskell indicates to me that there are things
>> people want to do with macros that aren't reasonably done in Haskell.  I
>> don't even know if I've ever wanted to do these things, because people
>> rarely miss language features that they don't know.
> 
> A language feature is not worth having unless it meets a need which 
> exists independent of anyone thinking to create said language feature. 

Obviously--but that doesn't mean that what those features should look
like is obvious, or even that people always know that difficulties
they're having can be solved by a language feature.  Sometimes you don't
know you have a problem until you see the solution, but that doesn't
mean you didn't have the problem in the first place.

> If you follow links below and poke around the Cliki you can locate those 
> folks who got to Lisp via the Greenspun route in some way shape or form, 
> people who were trying to do Lisp, not knowing there was such a thing.

I was wondering who this Greenspun y'all seem to worship is, so I did a
Google search.  His list "nice languages" is "Haskell, ML, and Lisp".  I
doubt anyone is "trying to do Lisp" in Haskell.

Jesse
-- 
"A hungry man is not a free man."      --Adlai Stevenson
From: Kenny Tilton
Subject: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <rV%ob.29507$Gq.8190280@twister.nyc.rr.com>
Peter Seibel wrote:
> Joachim Durchholz <·················@web.de> writes:
> 
> 
>>Peter Seibel wrote:
>>
>>
>>>Joachim Durchholz <·················@web.de> writes:
>>and I not just suspect but know that macros have some very serious
>>disadvantages (such as bad debugger interaction, a potential for
>>really ugly hairballs, and a constant temptation for stopgap
>>solutions that "work well enough").
> 
> 
> Well, of those the debugger interaction is perhaps the most serious.
> Yet in practice (Hey Pascal, I almost said "in 99% of cases"!) it
> doesn't seem to be that much of a problem. Maybe that's because we've
> just learned to deal with the pain; maybe MACROEXPAND is all you
> really need to get your bearings. At any rate, there's no in principle
> that a Lisp implementation couldn't keep track of macro information
> along with the compiled code just the way most compiler keep track of
> line number information in order to show you the code as written in
> the debugger. (And if it was really slick to let you step through the
> macro expansion, etc.)

Cue Duane of Franz. He mentioned over lunch at ILC2003 where John 
McCarthy used my laptop for ten minutes that their Allegro Common Lisp 
product was going to exactly that, including the expansion thing. I 
think he also said something about expanding in steps, but I did not 
quite follow. I suppose it is like stepping into a function or not, 
except the question here is whether nested macros get expanded (and you 
then get to step through those).

kenny

-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Duane Rettig
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <4wuaj84x5.fsf@franz.com>
Kenny Tilton <·······@nyc.rr.com> writes:

> Peter Seibel wrote:
> > Joachim Durchholz <·················@web.de> writes:
> >
> 
> >>Peter Seibel wrote:
> >>
> >>
> >>>Joachim Durchholz <·················@web.de> writes:
> >>and I not just suspect but know that macros have some very serious
> >>disadvantages (such as bad debugger interaction, a potential for
> >>really ugly hairballs, and a constant temptation for stopgap
> >>solutions that "work well enough").
> > Well, of those the debugger interaction is perhaps the most serious.
> 
> > Yet in practice (Hey Pascal, I almost said "in 99% of cases"!) it
> > doesn't seem to be that much of a problem. Maybe that's because we've
> > just learned to deal with the pain; maybe MACROEXPAND is all you
> > really need to get your bearings. At any rate, there's no in principle
> > that a Lisp implementation couldn't keep track of macro information
> > along with the compiled code just the way most compiler keep track of
> > line number information in order to show you the code as written in
> > the debugger. (And if it was really slick to let you step through the
> > macro expansion, etc.)
> 
> Cue Duane of Franz. He mentioned over lunch at ILC2003 where John
> McCarthy used my laptop for ten minutes that their Allegro Common Lisp
> product was going to exactly that, including the expansion thing. I
> think he also said something about expanding in steps, but I did not
> quite follow. I suppose it is like stepping into a function or not,
> except the question here is whether nested macros get expanded (and
> you then get to step through those).

Well, yes, but not for another release or so - I've got to get
environments access working right first (where do you think all
of this info and capability will be coming from? :-)

It is indeed true that macros tend to be opaque, and experience
with the best of C/C++ debuggers and those of other lanuages with
macro systems will simply reinforce this fact.  However, Common Lisp
macros tend not to be opaque (it is one of the more useful parts of
the fact that CL macros work on the same data that programs work on),
and one can see what a macro doing by simply macroexpanding it - for
example, try (pprint (macroexpand '(dotimes (i 10) (print i)))) in
a CL listener.  With this much openness, it doesn't seem unreasonable
to expect a debugger to be able to use such information to make macros
and the forms they expand into completely debuggable and steppable at
any desired level.

-- 
Duane Rettig    ·····@franz.com    Franz Inc.  http://www.franz.com/
555 12th St., Suite 1450               http://www.555citycenter.com/
Oakland, Ca. 94607        Phone: (510) 452-2000; Fax: (510) 452-0182   
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <pan.2003.11.02.11.00.33.369737@knm.org.pl>
On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:

> With this much openness, it doesn't seem unreasonable
> to expect a debugger to be able to use such information to make macros
> and the forms they expand into completely debuggable and steppable at
> any desired level.

Does any debugger do this?

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Duane Rettig
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <4vfq23i2m.fsf@franz.com>
Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:

> On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:
> 
> > With this much openness, it doesn't seem unreasonable
> > to expect a debugger to be able to use such information to make macros
> > and the forms they expand into completely debuggable and steppable at
> > any desired level.
> 
> Does any debugger do this?

Most Lisp debuggers will do this with compiled code.  I know of nne which
do this to compiled code without recompilation.

I apologize for the lack of context in my reply - it was late last night
and I have no time this morning as well; Lisp, and in particular CL, does
very well in debugging interpreted code.  However, just as I detest the
need for a -g option in gcc, I always strive to avoid requiring the
user to recompile in order to get debugging info.  In CL, the debug
quality interacts with but is separate from the speed, safety,
compilation-speed, and space qualities.

-- 
Duane Rettig    ·····@franz.com    Franz Inc.  http://www.franz.com/
555 12th St., Suite 1450               http://www.555citycenter.com/
Oakland, Ca. 94607        Phone: (510) 452-2000; Fax: (510) 452-0182   
From: ·············@comcast.net
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <vfq2lofj.fsf@comcast.net>
Duane Rettig <·····@franz.com> writes:

> Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:
>
>> On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:
>> 
>> > With this much openness, it doesn't seem unreasonable
>> > to expect a debugger to be able to use such information to make macros
>> > and the forms they expand into completely debuggable and steppable at
>> > any desired level.
>> 
>> Does any debugger do this?
>
> Most Lisp debuggers will do this with compiled code.  I know of none which
> do this to compiled code without recompilation.

MIT Scheme (which we all know is not Common Lisp) keeps around enough
debug information to determine the source code being executed at each
step in the compiled code.  I don't recall if there is a compiled code
stepper per se, but crawling down the stack in compiled code shows the
source code that was being evaluated.

-- 
~jrm, who personally knows someone who had an intimidating lunch
with John McCarthy
From: Fergus Henderson
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskellmacros]
Date: 
Message-ID: <3fa5d5e7$1@news.unimelb.edu.au>
·············@comcast.net writes:

>Duane Rettig <·····@franz.com> writes:
>
>> Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:
>>
>>> On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:
>>> 
>>> > With this much openness, it doesn't seem unreasonable
>>> > to expect a debugger to be able to use such information to make macros
>>> > and the forms they expand into completely debuggable and steppable at
>>> > any desired level.
>>> 
>>> Does any debugger do this?
>>
>> Most Lisp debuggers will do this with compiled code.  I know of none which
>> do this to compiled code without recompilation.
>
>MIT Scheme (which we all know is not Common Lisp) keeps around enough
>debug information to determine the source code being executed at each
>step in the compiled code.  I don't recall if there is a compiled code
>stepper per se, but crawling down the stack in compiled code shows the
>source code that was being evaluated.

Including macros invocations?

When you say "source code", do you really mean source code, or do
you mean the results of macro-expansion?

If I have a function foo whose body invokes a macro bar which calls a
function baz, can I get a "stack trace" or equivalent which shows me the
line in the definition of bar which invokes baz, and the line in the
definition of foo which invokes bar?  Can I see the bindings of the
parameters of bar?

(It would be great if I could, and there's no serious practical obstacle
AFAIK, but I don't know of any debuggers that actually do that.)

-- 
Fergus Henderson <···@cs.mu.oz.au>  |  "I have always known that the pursuit
The University of Melbourne         |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.
From: ·············@comcast.net
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskellmacros]
Date: 
Message-ID: <d6c9z63v.fsf@comcast.net>
Fergus Henderson <···@cs.mu.oz.au> writes:

> ·············@comcast.net writes:
>
>>Duane Rettig <·····@franz.com> writes:
>>
>>> Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:
>>>
>>>> On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:
>>>> 
>>>> > With this much openness, it doesn't seem unreasonable
>>>> > to expect a debugger to be able to use such information to make macros
>>>> > and the forms they expand into completely debuggable and steppable at
>>>> > any desired level.
>>>> 
>>>> Does any debugger do this?
>>>
>>> Most Lisp debuggers will do this with compiled code.  I know of none which
>>> do this to compiled code without recompilation.
>>
>>MIT Scheme (which we all know is not Common Lisp) keeps around enough
>>debug information to determine the source code being executed at each
>>step in the compiled code.  I don't recall if there is a compiled code
>>stepper per se, but crawling down the stack in compiled code shows the
>>source code that was being evaluated.
>
> Including macros invocations?

I don't think MIT Scheme tracks macro expansions.

However, PLT Scheme does.  The compiler and macroexpander are
orthogonal, so in principle one could simply merge the two methods.

> When you say "source code", do you really mean source code, or do
> you mean the results of macro-expansion?

In PLT Scheme I really mean the source code.

> If I have a function foo whose body invokes a macro bar which calls a
> function baz, can I get a "stack trace" or equivalent which shows me the
> line in the definition of bar which invokes baz, and the line in the
> definition of foo which invokes bar?  Can I see the bindings of the
> parameters of bar?

(define (baz x)
  (+ x 3))

(define-syntax bar
  (syntax-rules ()
    ((bar x) (begin0 (baz x) #f))))

(define (foo y)
  (begin (bar y) #f))

> (foo 'a)

+: expects type <number> as 1st argument, given: a; other arguments were: 3
c:\home\jrm\test.ss:3:2: (+ x 3)
c:\home\jrm\test.ss:10:9: (begin0 (baz y) #f)
STDIN::105: (foo (quote a))
From: Fergus Henderson
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskellmacros]
Date: 
Message-ID: <3fa6b238$1@news.unimelb.edu.au>
·············@comcast.net writes:

>Fergus Henderson <···@cs.mu.oz.au> writes:
>
>> If I have a function foo whose body invokes a macro bar which calls a
>> function baz, can I get a "stack trace" or equivalent which shows me the
>> line in the definition of bar which invokes baz, and the line in the
>> definition of foo which invokes bar?  Can I see the bindings of the
>> parameters of bar?
>
>(define (baz x)
>  (+ x 3))
>
>(define-syntax bar
>  (syntax-rules ()
>    ((bar x) (begin0 (baz x) #f))))
>
>(define (foo y)
>  (begin (bar y) #f))
>
>> (foo 'a)
>
>+: expects type <number> as 1st argument, given: a; other arguments were: 3
>c:\home\jrm\test.ss:3:2: (+ x 3)
>c:\home\jrm\test.ss:10:9: (begin0 (baz y) #f)
>STDIN::105: (foo (quote a))

That's still missing an entry from the stack trace.
There's no entry for the call to bar.

-- 
Fergus Henderson <···@cs.mu.oz.au>  |  "I have always known that the pursuit
The University of Melbourne         |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.
From: james anderson
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <3FA5027D.5FDFB4AB@setf.de>
Marcin 'Qrczak' Kowalczyk wrote:
> 
> On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:
> 
> > With this much openness, it doesn't seem unreasonable
> > to expect a debugger to be able to use such information to make macros
> > and the forms they expand into completely debuggable and steppable at
> > any desired level.
> 
> Does any debugger do this?

? you mean like this? wrt evaluating

(defun testf (x)
  (dotimes (i x)
    (print i)))

(step (testf 2))

==>

(testf 2)
  (block testf (dotimes (i x) (print i)))
    (dotimes (i x) (print i))
      x = 2
      (block nil (if (ccl::int>0-p #:g25) (tagbody #:g24 (print i) (locally #
#) (unless # #))) nil)
        (if (ccl::int>0-p #:g25) (tagbody #:g24 (print i) (locally (declare #)
(setq i #)) (unless (eql i #:g25) (go #:g24))))
          (ccl::int>0-p #:g25)
            #:g25 = 2
          t
          (tagbody #:g24 (print i) (locally (declare (ccl::settable i)) (setq
i (1+ i))) (unless (eql i #:g25) (go #:g24)))
            (print i)
              i = 0
            0
            (locally (declare (ccl::settable i)) (setq i (1+ i)))
              (setq i (1+ i))
                (1+ i)
                  i = 0
                1
              1
            1
            (unless (eql i #:g25) (go #:g24))
              (not (eql i #:g25))
                (eql i #:g25)
                  i = 1
                  #:g25 = 2
                nil
              t
              (progn (go #:g24))
                (go #:g24)
            (print i)
              i = 1
            1
            (locally (declare (ccl::settable i)) (setq i (1+ i)))
              (setq i (1+ i))
                (1+ i)
                  i = 1
                2
              2
            2
            (unless (eql i #:g25) (go #:g24))
              (not (eql i #:g25))
                (eql i #:g25)
                  i = 2
                  #:g25 = 2
                t
              nil
            nil
          nil
        nil
      nil
    nil
  nil
nil


v/s

(testf 2)
  (block testf (dotimes (i x) (print i)))
    (dotimes (i x) (print i))
    nil
  nil
nil


depending on whether one stepped into or over the macro form?
From: Duane Rettig
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <4r80q3hvs.fsf@franz.com>
james anderson <··············@setf.de> writes:

> Marcin 'Qrczak' Kowalczyk wrote:
> > 
> > On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:
> > 
> > > With this much openness, it doesn't seem unreasonable
> > > to expect a debugger to be able to use such information to make macros
> > > and the forms they expand into completely debuggable and steppable at
> > > any desired level.
> > 
> > Does any debugger do this?
> 
> ? you mean like this? wrt evaluating
> 
> (defun testf (x)
>   (dotimes (i x)
>     (print i)))
> 
> (step (testf 2))

I've reproduced the whole code below so that readers can see it
when they contemplate this comment and a question (I have no time
now, but I'll explain tonight if nobody gets it, although it should
be easy):  James did not say what lisp he was using, but presumably
it is a Common Lisp.  The following example was obviously not
compiled.  Can you explain why?

> ==>
> 
> (testf 2)
>   (block testf (dotimes (i x) (print i)))
>     (dotimes (i x) (print i))
>       x = 2
>       (block nil (if (ccl::int>0-p #:g25) (tagbody #:g24 (print i) (locally #
> #) (unless # #))) nil)
>         (if (ccl::int>0-p #:g25) (tagbody #:g24 (print i) (locally (declare #)
> (setq i #)) (unless (eql i #:g25) (go #:g24))))
>           (ccl::int>0-p #:g25)
>             #:g25 = 2
>           t
>           (tagbody #:g24 (print i) (locally (declare (ccl::settable i)) (setq
> i (1+ i))) (unless (eql i #:g25) (go #:g24)))
>             (print i)
>               i = 0
>             0
>             (locally (declare (ccl::settable i)) (setq i (1+ i)))
>               (setq i (1+ i))
>                 (1+ i)
>                   i = 0
>                 1
>               1
>             1
>             (unless (eql i #:g25) (go #:g24))
>               (not (eql i #:g25))
>                 (eql i #:g25)
>                   i = 1
>                   #:g25 = 2
>                 nil
>               t
>               (progn (go #:g24))
>                 (go #:g24)
>             (print i)
>               i = 1
>             1
>             (locally (declare (ccl::settable i)) (setq i (1+ i)))
>               (setq i (1+ i))
>                 (1+ i)
>                   i = 1
>                 2
>               2
>             2
>             (unless (eql i #:g25) (go #:g24))
>               (not (eql i #:g25))
>                 (eql i #:g25)
>                   i = 2
>                   #:g25 = 2
>                 t
>               nil
>             nil
>           nil
>         nil
>       nil
>     nil
>   nil
> nil
> 
> 
> v/s
> 
> (testf 2)
>   (block testf (dotimes (i x) (print i)))
>     (dotimes (i x) (print i))
>     nil
>   nil
> nil
> 
> 
> depending on whether one stepped into or over the macro form?

-- 
Duane Rettig    ·····@franz.com    Franz Inc.  http://www.franz.com/
555 12th St., Suite 1450               http://www.555citycenter.com/
Oakland, Ca. 94607        Phone: (510) 452-2000; Fax: (510) 452-0182   
From: james anderson
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <3FA52C13.CF9DE444@setf.de>
Duane Rettig wrote:
> 
> james anderson <··············@setf.de> writes:
> 
> > Marcin 'Qrczak' Kowalczyk wrote:
> > >
> > > On Sun, 02 Nov 2003 02:01:58 -0800, Duane Rettig wrote:
> > >
> > > > With this much openness, it doesn't seem unreasonable
> > > > to expect a debugger to be able to use such information to make macros
> > > > and the forms they expand into completely debuggable and steppable at
> > > > any desired level.
> > >
> > > Does any debugger do this?
> >
> > ? you mean like this? wrt evaluating
> >
> > (defun testf (x)
> >   (dotimes (i x)
> >     (print i)))
> >
> > (step (testf 2))
> 
> I've reproduced the whole code below so that readers can see it
> when they contemplate this comment and a question (I have no time
> now, but I'll explain tonight if nobody gets it, although it should
> be easy):  James did not say what lisp he was using, but presumably
> it is a Common Lisp.  The following example was obviously not
> compiled.  Can you explain why?
> 
> > ==>
> >...
> >
> > v/s
> >
> > ...
> >
> > depending on whether one stepped into or over the macro form?

yes. whereby the first transcript is the result of successive "steps into".

...
From: james anderson
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <3FA50418.49F2878D@setf.de>
Duane Rettig wrote:
> 
> ...
> 
> Well, yes, but not for another release or so - I've got to get
> environments access working right first (where do you think all
> of this info and capability will be coming from? :-)
> 

just out of curiosity, what it the benefit of using environemnts for this
rather than integrating it into comiled code vectors? could it then be applied
retrospectively, independant of how the code was compiled?

...
From: Shriram Krishnamurthi
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <w7dk76ilujp.fsf@cs.brown.edu>
[Newsgroups header severly restricted.]

Kenny Tilton <·······@nyc.rr.com> writes:

> Cue Duane of Franz. He mentioned over lunch at ILC2003 where John
> McCarthy used my laptop for ten minutes that [...]

Kenny: Have you considered writing a keyboard macro for Emacs that will
automatically insert "used my laptop for ten minutes" whenever it sees
"John McCarthy"?  Surely McCarthy wouldn't approve of all this
repetitive typing.

Shriram (who once had a very intimidating lunch with John McCarthy)
From: Pascal Bourguignon
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <87n0bfhszi.fsf@thalassa.informatimago.com>
Kenny Tilton <·······@nyc.rr.com> writes:
> Cue Duane of Franz. He mentioned over lunch at ILC2003 where John
> McCarthy used my laptop for ten minutes that their Allegro Common Lisp

Just put "John McCarthy used my laptop for ten minutes" in your
signature and forget it! :-)


-- 
__Pascal_Bourguignon__
http://www.informatimago.com/
From: Kenny Tilton
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <GS9pb.30687$Gq.8381335@twister.nyc.rr.com>
Pascal Bourguignon wrote:

> Kenny Tilton <·······@nyc.rr.com> writes:
> 
>>Cue Duane of Franz. He mentioned over lunch at ILC2003 where John
>>McCarthy used my laptop for ten minutes that their Allegro Common Lisp
> 
> 
> Just put "John McCarthy used my laptop for ten minutes" in your
> signature and forget it! :-)

I prefer the subliminal approach, it affects brain Cells more indelibly.

How about JMUML?

:)

kenny

-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Espen Vestre
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <kwbrrt7sys.fsf@merced.netfonds.no>
Kenny Tilton <·······@nyc.rr.com> writes:

> I prefer the subliminal approach, it affects brain Cells more indelibly.
> 
> How about JMUML?

Hmm. Does this call for something like the Erd�s numbers?

http://www.oakland.edu/~grossman/erdoshp.html

;-)
-- 
  (espen)
From: Pascal Bourguignon
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <87vfq1zf0h.fsf@thalassa.informatimago.com>
Espen Vestre <·····@*do-not-spam-me*.vestre.net> writes:

> Kenny Tilton <·······@nyc.rr.com> writes:
> 
> > I prefer the subliminal approach, it affects brain Cells more indelibly.
> > 
> > How about JMUML?
> 
> Hmm. Does this call for something like the Erd�s numbers?
> 
> http://www.oakland.edu/~grossman/erdoshp.html
> 
> ;-)

Most probably.   Kenny, your laptop adquired an  incredibly high value
on ebay!  What a smart move!

The question  now is if I would  get a McCathy number  by having Kenny
use my laptop, or by my using Kenny's laptop?

-- 
__Pascal_Bourguignon__
http://www.informatimago.com/
From: Jens Axel Søgaard
Subject: Re: Paging Mr. Rettig [ws Re: Explanation of macros; Haskell macros]
Date: 
Message-ID: <3fa66ba3$0$69913$edfadb0f@dread12.news.tele.dk>
Pascal Bourguignon wrote:
> Most probably.   Kenny, your laptop adquired an  incredibly high value
> on ebay!  What a smart move!

;-)

> The question  now is if I would  get a McCathy number  by having Kenny
> use my laptop, or by my using Kenny's laptop?

<http://groups.google.com/groups?hl=en&lr=&ie=UTF-8&th=6603f280cd83277e&rnum=1>

-- 
Jens Axel S�gaard
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo5r9t$tdq$1@news.oberberg.net>
Peter Seibel wrote:

> Joachim Durchholz <·················@web.de> writes:
> 
>>Peter Seibel wrote:
>>
>>>Joachim Durchholz <·················@web.de> writes:
>>>
>>>>And, of course, macros can evaluate at compile time. Personally, I'd
>>>>prefer to do compile-time evaluation based on "the compiler will
>>>>evaluate all known-to-be-constant expressions". The advantage here
>>>>is that programmers don't need to learn another sublanguage for
>>>>compile-time expressions.
>>>
>>>Ah, but in Lisp we don't have to. We use Lisp.
>>
>>Having readers and special forms /is/ an extra sublanguage. I don't
>>have to learn extra syntax for these forms (which is good), but I do
>>have to learn about a lot of special rules that apply to macros and
>>nothing else (which is not so good).
> 
> Hmmmm. The special forms (25 of them, called special operators these
> days, by the by) are used the same in macros and functions. Lisp's
> customizable reader is a separate thing--there is no need to customize
> the reader to write macros.

You're right, and made me rethink what's actually disturbing me about 
macros.

Perhaps it's that I have to adapt to dual-mode (two-tier?) thinking: I 
have to reason about both what the macros are doing and what the 
software is doing.
Alternatively, I could consider the macros as "part of the language" and 
not reason about the macro code but about their effects - in which case 
I have effectively augmented the language by all macros that are in use.

Personally, I'd still prefer a compiler that's evaluating constant 
expression.

Is there anything that a macro does that can't be done by preevaluating 
data structures that contain functions (or closures)? At first glance, 
I'd say no, but then I don't know what macros are used for in practice.

Um, well, yes, there is one thing that macros can do: extending syntax 
in ways that aren't part of the original language syntax. E.g. replacing 
all those parentheses by indentation, or something similar un-Lispish.
(Extending syntax in such ways is a mistake IMHO, but YMMV. Anyway, I'm 
more interested in the question if there's any /semantics/ that can be 
done via macros but not via compile-time evaluation.)

>>Letting the compiler evaluate what it can means that I don't even
>>have to learn extra forms.
> 
> I'm not sure what "extra" forms you're talking about. Other than
> DEFMACRO, I guess. But by that argument we'd be better off without
> DEFUN too because that's just another darn thing to learn.

I believe it's not DEFMACRO that's complicating things, it's the macros 
that it allows (see above).

>>I just suspect that better solutions are available in every case,
> 
> Interesting. A lot of people suspect that who haven't actually used
> Common Lisp macros. Yet almost all Common Lispers--who by in large are
> *not* monolinguists--think macros are one of Common Lisp's great
> features. I'm not saying your wrong, but if those better solutions are
> out there for all the things I can do with macros, I haven't seen
> them. Now I don't know Haskell or ML so I'm also suffering from finite
> knowledge. Maybe one day I'll have time to learn one of them for
> myself and see if they really do offer better solutions.

Agreed on all accounts (except that I don't know how "multilingual" 
Lispers really are *g*).

Does anybody have a keyword-style list of useful applications of the 
macro facilities?

>>and I not just suspect but know that macros have some very serious
>>disadvantages (such as bad debugger interaction, a potential for
>>really ugly hairballs, and a constant temptation for stopgap
>>solutions that "work well enough").
> 
> Well, of those the debugger interaction is perhaps the most serious.
> Yet in practice (Hey Pascal, I almost said "in 99% of cases"!)

"99% of all cases" is a pretty good argument actually :-)
It's just that Pascal doesn't (want to) believe that it's enough for 
type checking. His problem, not mine...

 > it
> doesn't seem to be that much of a problem. Maybe that's because we've
> just learned to deal with the pain; maybe MACROEXPAND is all you
> really need to get your bearings. At any rate, there's no in principle
> that a Lisp implementation couldn't keep track of macro information
> along with the compiled code just the way most compiler keep track of
> line number information in order to show you the code as written in
> the debugger. (And if it was really slick to let you step through the
> macro expansion, etc.)

Agreed.
I'm getting more and more convinced that it's not language size or KISS 
issues that's setting me off, it's that "two-tier thinking" that I 
(perhaps mistakenly?) associate with macros.

>>Lisp-the-language is a quite pretty lean-and-mean KISS language. The
>>stuff that's built on top of it (macros, readers, dispatch
>>mechanisms, etc. etc.) is neither lean nor KISS nor (IMHO) pretty -
>>YMMV.
> 
> Clearly. I find Common Lisp to be a pretty beautiful piece of
> *engineering*.  Which may be different than a beautiful realization of
> a beautiful theory.

I wouldn't want HM typing if it were just beautiful theory.
HM typing happens to be a beautiful theory. Things are getting less 
beautiful once you interact with the Real World (TM), which is stateful 
- OTOH, Real World is a mess, so don't expect computing to be beautiful 
anymore when there is interaction with it *g*. What surprised me is how 
much of a computation can be separated from such interaction. With the 
proper framework, one can even describe interaction patterns (which are 
themselves stateless), feed these patterns to the framework, and watch 
in amazement how the execution engine follows these patterns. It's the 
kind of abstractive facility I've been yearning for decades...
Lisp could do this just as well. It's just not done because taking the 
shortcut and doing stateful computations directly is so much easier.
(And I don't pretend that functional languages are doing this kind of 
thing perfectly right now. I think the potential in these ideas is just 
beginning to be exploited - and what's available is already quite 
impressive.)

>>Or, more to the point: I have yet to see something that cannot be
>>done in a leaner, more KISS way.
> 
> Well, if I promise to continue to think that someday I really should
> learn a hard-core FP language so I can see what all the static typing
> fuss is about, will you promise to think in the back of your mind that
> maybe someday you should learn Common Lisp and see what makes us all
> so gaga over macros.

Actually I'm trying to understand macros and macro usage right now, 
without having to learn all the details of CL (which would be a bit of 
overkill - I know it might not be enough, but then my time is limited so 
I'm doing my best within the available budget).

Regards,
Jo
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3znfdidvt.fsf@javamonkey.com>
Joachim Durchholz <·················@web.de> writes:

> Peter Seibel wrote:
> 
> > Joachim Durchholz <·················@web.de> writes:
> >
> >>Peter Seibel wrote:
> >>
> >>>Joachim Durchholz <·················@web.de> writes:
> >>>
> >>>>And, of course, macros can evaluate at compile time. Personally, I'd
> >>>>prefer to do compile-time evaluation based on "the compiler will
> >>>>evaluate all known-to-be-constant expressions". The advantage here
> >>>>is that programmers don't need to learn another sublanguage for
> >>>>compile-time expressions.
> >>>
> >>>Ah, but in Lisp we don't have to. We use Lisp.
> >>
> >>Having readers and special forms /is/ an extra sublanguage. I don't
> >>have to learn extra syntax for these forms (which is good), but I do
> >>have to learn about a lot of special rules that apply to macros and
> >>nothing else (which is not so good).
> > Hmmmm. The special forms (25 of them, called special operators these
> > days, by the by) are used the same in macros and functions. Lisp's
> > customizable reader is a separate thing--there is no need to customize
> > the reader to write macros.
> 
> You're right, and made me rethink what's actually disturbing me about
> macros.
> 
> Perhaps it's that I have to adapt to dual-mode (two-tier?) thinking:
> I have to reason about both what the macros are doing and what the
> software is doing. Alternatively, I could consider the macros as
> "part of the language" and not reason about the macro code but about
> their effects - in which case I have effectively augmented the
> language by all macros that are in use.

I think you're right that you have to adopt a dual-mode of thinking.
When you're writing macros you're essentially extending the
compiler/language to recognize constructs that would otherwise be
meaningless.

Then, having written them, you use them as if they were in the
language all along. At one level this is no different from extending a
language by writing a function. That is, if you're working in a
language (like Common Lisp, Scheme, C, or--I imagine--any FPL) where
much of the "language" itself is implemented in terms of built-in
functions, if you write a new function you're extending the language
and after you've written it you can forget about the details of how it
works and just use it. The only difference between macros and
functions is that macros operate by generating code which then
performs actions as opposed to *being* code that performs actions. But
that level of indirection makes it easy to express things that would
otherwise be difficult (in my experience.)

> Personally, I'd still prefer a compiler that's evaluating constant
> expression.

Hmmm. If it will make you feel any better, macros are just fuctions
whose domain and range happens to be Lisp expressions. That happen to
be run by the compiler. So eventually the compiler is evaluating
constant expressions, just some of them were automatically derived
from the written source.

> Is there anything that a macro does that can't be done by
> preevaluating data structures that contain functions (or closures)?
> At first glance, I'd say no, but then I don't know what macros are
> used for in practice.

Well it depends whether you consider syntax to be "anything". I think
it was you who objected to one of my examples by saying, "that's just
syntactic sugar". Macros can (and many do) do large amount of
under-the-covers bookkeeping. For instance here are a few rules from a
grammar for a lexer for Java source code:

  (defprod line-terminator () (/ #\newline (#\return (? #\newline))))

  (defprod white-space () (/ #\space #\tab #\page line-terminator))

  (defprod input () ((* input-element) (? #\Sub)))

  (defprod input-element () (/ white-space comment token))

  (defprod token () (/ identifier java-keyword literal separator operator))

DEFPROD is a macro that squirrels away the stuff on the right which is
an s-expy form of BNF. The rest of the grammar is more of the same. At
the bottom of the grammar file where the productions are diffined I
have this form:

  (deflexer java-lexer (input)
    ((:tokens identifier java-keyword literal separator operator)))

That DEFLEXER call (another macro) expands into a single parsing
function built out of all the productions created by DEFPROD calls,
appropriately wired together and embedded into code that takes care of
the stepping through the input and gather up values, etc. And that
function is compiled into extremely efficient code because all the
intercommunication between productions goes through lexical variables.
And the file containing these calls to DEFPROD and DEFLEXER is legal
Lisp source which I can feed to the compiler and get native machine
code back.

So I don't know if that is "anything" or not. I don't know how I would
write such a thing in Haskell, et al. but I know this is a *lot*
cleaner than what *I'd* be able to do in Java, Perl, Python, or C.

> Um, well, yes, there is one thing that macros can do: extending
> syntax in ways that aren't part of the original language syntax.
> E.g. replacing all those parentheses by indentation, or something
> similar un-Lispish. (Extending syntax in such ways is a mistake
> IMHO, but YMMV. Anyway, I'm more interested in the question if
> there's any /semantics/ that can be done via macros but not via
> compile-time evaluation.)

Actually, changing the syntax is--if one thinks one must--is really
done by read-macros which are quite different. But most Lispers agree
with you--there's just not enough benefit to changing the syntax to be
worth it. Except for occasionally making a new syntax for expressing
certain frequently created literal objects that otherwise would
require a much more verbose creation form. (Someone gave a great
example the other day in another thread of an airline reservation
system (Orbitz I think) that has a special kind of object used to
represent the three-letter airport codes. Since they wanted to always
have the same object representing a given airport they needed to
intern the objets with the TLA as the key. But rather than writing
(intern-airport-code "BOS") everywhere, they wrote a reader macro that
let them write: #!BOS. Since this was an incredibly common operation
in their system, it was worth a tiny bit of new syntax. But note,
again, that's not *changing* the syntax so much as extending it.)

> >> Letting the compiler evaluate what it can means that I don't even
> >> have to learn extra forms.
> >
> > I'm not sure what "extra" forms you're talking about. Other than
> > DEFMACRO, I guess. But by that argument we'd be better off without
> > DEFUN too because that's just another darn thing to learn.
> 
> I believe it's not DEFMACRO that's complicating things, it's the
> macros that it allows (see above).

Fair enough. But do you object to the ability to write new functions
on the grounds that that just means you have a lot of new functions to
learn and that complicates things needlessly? That's obviously a
rhetorical question but I am actually curious why you find them
different, if you do.

> >>I just suspect that better solutions are available in every case,
> > Interesting. A lot of people suspect that who haven't actually used
> > Common Lisp macros. Yet almost all Common Lispers--who by in large are
> > *not* monolinguists--think macros are one of Common Lisp's great
> > features. I'm not saying your wrong, but if those better solutions are
> > out there for all the things I can do with macros, I haven't seen
> > them. Now I don't know Haskell or ML so I'm also suffering from finite
> > knowledge. Maybe one day I'll have time to learn one of them for
> > myself and see if they really do offer better solutions.
> 
> Agreed on all accounts (except that I don't know how "multilingual"
> Lispers really are *g*).

Well, there is the problem that once folks find Lisp they tend to stop
looking for better things because what could be better than Lisp. ;-)
But most Lispers take a fairly circuitous path to Lisp and hit a bunch
of other languages before they find it.

> Does anybody have a keyword-style list of useful applications of the
> macro facilities?
> 
> >>and I not just suspect but know that macros have some very serious
> >>disadvantages (such as bad debugger interaction, a potential for
> >>really ugly hairballs, and a constant temptation for stopgap
> >>solutions that "work well enough").
> > Well, of those the debugger interaction is perhaps the most serious.
> > Yet in practice (Hey Pascal, I almost said "in 99% of cases"!)
> 
> "99% of all cases" is a pretty good argument actually :-)
> It's just that Pascal doesn't (want to) believe that it's enough for
> type checking. His problem, not mine...
> 
>  > it
> > doesn't seem to be that much of a problem. Maybe that's because we've
> > just learned to deal with the pain; maybe MACROEXPAND is all you
> > really need to get your bearings. At any rate, there's no in principle
> > that a Lisp implementation couldn't keep track of macro information
> > along with the compiled code just the way most compiler keep track of
> > line number information in order to show you the code as written in
> > the debugger. (And if it was really slick to let you step through the
> > macro expansion, etc.)
> 
> Agreed. I'm getting more and more convinced that it's not language
> size or KISS issues that's setting me off, it's that "two-tier
> thinking" that I (perhaps mistakenly?) associate with macros.

The funny thing is to me, when you say "two-tier thinking" that
perfectly describes how I think about the process of making
abstractions. Regardless of the *kind* of abstraction one is creating,
one has to be facile at switching mental gears between *building* the
abstraction and *using* it. You are probably so used to doing this
when writing functions that you don't even notice the switch. But
because macros are a bit strange you *notice* the switching and it
annoys you. I suspect that anyone who's capable of building functional
abstractions would--if they actually used macros--quickly learn to
switch gears equally smoothly when writing and using macros.

> >>Lisp-the-language is a quite pretty lean-and-mean KISS language. The
> >>stuff that's built on top of it (macros, readers, dispatch
> >>mechanisms, etc. etc.) is neither lean nor KISS nor (IMHO) pretty -
> >>YMMV.
> > Clearly. I find Common Lisp to be a pretty beautiful piece of
> > *engineering*.  Which may be different than a beautiful realization of
> > a beautiful theory.
> 
> I wouldn't want HM typing if it were just beautiful theory.
> HM typing happens to be a beautiful theory. Things are getting less
> beautiful once you interact with the Real World (TM), which is
> stateful - OTOH, Real World is a mess, so don't expect computing to be
> beautiful anymore when there is interaction with it *g*. What
> surprised me is how much of a computation can be separated from such
> interaction. With the proper framework, one can even describe
> interaction patterns (which are themselves stateless), feed these
> patterns to the framework, and watch in amazement how the execution
> engine follows these patterns. It's the kind of abstractive facility
> I've been yearning for decades...
> Lisp could do this just as well. It's just not done because taking the
> shortcut and doing stateful computations directly is so much easier.
> (And I don't pretend that functional languages are doing this kind of
> thing perfectly right now. I think the potential in these ideas is
> just beginning to be exploited - and what's available is already quite
> impressive.)
> 
> >>Or, more to the point: I have yet to see something that cannot be
> >>done in a leaner, more KISS way.
> > Well, if I promise to continue to think that someday I really should
> > learn a hard-core FP language so I can see what all the static typing
> > fuss is about, will you promise to think in the back of your mind that
> > maybe someday you should learn Common Lisp and see what makes us all
> > so gaga over macros.
> 
> Actually I'm trying to understand macros and macro usage right now,
> without having to learn all the details of CL (which would be a bit of
> overkill - I know it might not be enough, but then my time is limited
> so I'm doing my best within the available budget).

Sure. Cheers.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo6603$d4d$1@news.oberberg.net>
Peter Seibel wrote:

>> Personally, I'd still prefer a compiler that's evaluating constant 
>> expression.
> 
> Hmmm. If it will make you feel any better, macros are just fuctions 
> whose domain and range happens to be Lisp expressions. That happen to
>  be run by the compiler. So eventually the compiler is evaluating 
> constant expressions, just some of them were automatically derived 
> from the written source.

Hmm... you're right here.
The HOF approach has one advantage over the DEFMACRO approach: code
written using HOFs will automagically adapt if some of the constant
inputs become variable, or vice versa. For DEFMACRO, if a constant
becomes input, the macro will become inapplicable and the source code
will have to change; for HOFs, the compiler will be able to
automatically adapt.

>> Is there anything that a macro does that can't be done by 
>> preevaluating data structures that contain functions (or closures)?
>>  At first glance, I'd say no, but then I don't know what macros are
>>  used for in practice.
> 
> Well it depends whether you consider syntax to be "anything". I think
>  it was you who objected to one of my examples by saying, "that's
> just syntactic sugar". Macros can (and many do) do large amount of 
> under-the-covers bookkeeping. For instance here are a few rules from
> a grammar for a lexer for Java source code:
> 
> (defprod line-terminator () (/ #\newline (#\return (? #\newline))))
> 
> (defprod white-space () (/ #\space #\tab #\page line-terminator))
> 
> (defprod input () ((* input-element) (? #\Sub)))
> 
> (defprod input-element () (/ white-space comment token))
> 
> (defprod token () (/ identifier java-keyword literal separator
> operator))
> 
> DEFPROD is a macro that squirrels away the stuff on the right which
> is an s-expy form of BNF. The rest of the grammar is more of the
> same. At the bottom of the grammar file where the productions are
> diffined I have this form:
> 
> (deflexer java-lexer (input) ((:tokens identifier java-keyword
> literal separator operator)))
> 
> That DEFLEXER call (another macro) expands into a single parsing 
> function built out of all the productions created by DEFPROD calls, 
> appropriately wired together and embedded into code that takes care
> of the stepping through the input and gather up values, etc. And that
>  function is compiled into extremely efficient code because all the 
> intercommunication between productions goes through lexical
> variables. And the file containing these calls to DEFPROD and
> DEFLEXER is legal Lisp source which I can feed to the compiler and
> get native machine code back.
> 
> So I don't know if that is "anything" or not.

It most definitely is "something" :-)

> I don't know how I would write such a thing in Haskell, et al. but I
> know this is a *lot* cleaner than what *I'd* be able to do in Java,
> Perl, Python, or C.

I'm looking at things from a Haskell perspective.

Actually, functional languages do similar things; it's called
"combinator parsing".
The basic approach is this: you have parsing functions that each
recognize a particular language, trivial parsers that each recognize
just one element of the alphabet, and parser combinators that take one,
two, or more subparsers and combine them into a bigger one (for
constructing alternatives, options, repetitions and whatever your
personal flavor of BNF can do).

I don't know enough about any approach to do an in-detail comparison,
but the rough picture seems to be pretty similar.

Downside of combinator parsing: it's difficult to get bottom-up parsers
done that way. Also, simple-minded combinator parsers tend to do
backtracking, though it's not very difficult to make the combinators
diagnose and report violations of LL(whatever) properties.

Ah - I see one other thing that HOFs cannot do: issue compile-time error
messages.
Unless, of course, there is a data type that, when evaluated at compile
time, causes the compiler to emit an error message... not /that/
difficult to do, but might require some careful thought to make the
mechanism interact well with other properties of the language.

>> Um, well, yes, there is one thing that macros can do: extending 
>> syntax in ways that aren't part of the original language syntax. 
>> E.g. replacing all those parentheses by indentation, or something 
>> similar un-Lispish. (Extending syntax in such ways is a mistake 
>> IMHO, but YMMV. Anyway, I'm more interested in the question if 
>> there's any /semantics/ that can be done via macros but not via 
>> compile-time evaluation.)
> 
> Actually, changing the syntax is--if one thinks one must--is really 
> done by read-macros which are quite different. But most Lispers agree
>  with you--there's just not enough benefit to changing the syntax to
> be worth it.

OK.

> Except for occasionally making a new syntax for expressing certain
> frequently created literal objects that otherwise would require a
> much more verbose creation form. (Someone gave a great example the
> other day in another thread of an airline reservation system (Orbitz
> I think) that has a special kind of object used to represent the
> three-letter airport codes. Since they wanted to always have the same
> object representing a given airport they needed to intern the objets
> with the TLA as the key. But rather than writing (intern-airport-code
> "BOS") everywhere, they wrote a reader macro that let them write:
> #!BOS. Since this was an incredibly common operation in their system,
> it was worth a tiny bit of new syntax. But note, again, that's not
> *changing* the syntax so much as extending it.)

In my book, "extending" isn't so much different than "changing".
I agree it's the kind of worthwhile change that makes sense.
In Haskell, one would probably have an "Airport" module that defined
these codes, and write something like
   TLA "BOS"
which is more syntax than #!BOS but seems good enough for me. (YMMV.)

>>>> Letting the compiler evaluate what it can means that I don't
>>>> even have to learn extra forms.
>>> 
>>> I'm not sure what "extra" forms you're talking about. Other than 
>>> DEFMACRO, I guess. But by that argument we'd be better off
>>> without DEFUN too because that's just another darn thing to
>>> learn.
>> 
>> I believe it's not DEFMACRO that's complicating things, it's the 
>> macros that it allows (see above).
> 
> Fair enough. But do you object to the ability to write new functions 
> on the grounds that that just means you have a lot of new functions
> to learn and that complicates things needlessly? That's obviously a 
> rhetorical question but I am actually curious why you find them 
> different, if you do.

It's just the KISS principle: why two abstraction facilities (macros and
functions) if one suffices?
Provided that functions suffice, actually :-)

>> Agreed. I'm getting more and more convinced that it's not language 
>> size or KISS issues that's setting me off, it's that "two-tier 
>> thinking" that I (perhaps mistakenly?) associate with macros.
> 
> The funny thing is to me, when you say "two-tier thinking" that 
> perfectly describes how I think about the process of making 
> abstractions. Regardless of the *kind* of abstraction one is
> creating, one has to be facile at switching mental gears between
> *building* the abstraction and *using* it. You are probably so used
> to doing this when writing functions that you don't even notice the
> switch.

Hmm... not consciously, but there is certainly a difference.
It seems to be smaller with functional languages, particularly if you're
working at higher levels.
In an FPL with proper syntactical minimalism, programming enters a
"we're sticking functions together" style, which partially abstracts
away the parameters (at least as entities you're conscious about). I.e.
the "using abstractions" thinking mode diminishes. (I'm not far enough
into that style to say how this works after that style was fully adopted.)

> But because macros are a bit strange you *notice* the switching and
> it annoys you. I suspect that anyone who's capable of building
> functional abstractions would--if they actually used macros--quickly
> learn to switch gears equally smoothly when writing and using macros.
> 
Possibly... can't tell.

Regards,
Jo
From: Pascal Costanza
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo5udk$oj5$1@newsreader2.netcologne.de>
Joachim Durchholz wrote:

> Is there anything that a macro does that can't be done by preevaluating 
> data structures that contain functions (or closures)? At first glance, 
> I'd say no, but then I don't know what macros are used for in practice.

Macros are mainly used for abstracting away details of sophisticated 
protocols. For me, the "Hello, World" of macro programming is this:

When you want to bind to a resource, you usually have to make sure that 
you also unbind again later on. The standard pattern in many languages, 
modulo syntactic variations, is this:

try: bind resource
      do something
finally: unbind resource


The fact that you need to place the unbind in a finally statement 
reflects the requirement a protocol imposes on the use of rources: You 
have to make sure to execute the necessay steps in a certain order, and 
you have to make sure that certain steps are always executed, no matter 
what. There are lots of examples like this in programming, and 
especially more complicated ones.

A macro allows you to abstract away from this. The same code, in a 
language with macro support, would look like this:

with-bound-resorce:
   do something

The macro "with-bound-resource" takes care of executing the right steps 
at the right time.

Now, this is admittedly not an example for a particularly sophisticated 
protocol. Therefore, one of the usual gut reactions from people who are 
not used to macros yet is "but I can do this with higher order functions!"

However, what this example already shows is: The with-bound-resource 
macro doesn't tell you anything about how it achieves its goals. Yes, 
the natural way to implement this example is with a HOF, but you could 
also use a completely different approach. _With macros you can build 
abstractions that completely hide their implementation details._

This becomes especially useful as soon as your protocols become more 
sophisticated, and you need to insert instructions at arbitrary places 
in the code being passed to a macro, or need to control evaluation of 
the code being passed in some other details.

Because of this high level of expressive power that macros provide, 
Common Lispers use them regularly even for simple things. You can 
effectively write domain-specific abstractions that don't leak, and 
therefore it is justified to use them even for simple protocols.

> Um, well, yes, there is one thing that macros can do: extending syntax 
> in ways that aren't part of the original language syntax. E.g. replacing 
> all those parentheses by indentation, or something similar un-Lispish.
> (Extending syntax in such ways is a mistake IMHO, but YMMV. Anyway, I'm 
> more interested in the question if there's any /semantics/ that can be 
> done via macros but not via compile-time evaluation.)

Compile-time evaluation is a red herring. Macros do their job by 
rewriting abstract syntax trees. (Lisp and macros go very well together 
because in Lisp, you essentially program using a notation that maps 
directly to an internal syntax tree, nearly without any parsing overhead.)

Since the syntax tree is usually available at compile time, that's the 
natural time to let macros do their job. However, in theory it wouldn't 
be a problem to use macro expansion at runtime.

(In Common Lisp, this is already possible in limited ways: an 
interpreted implementation of Common Lisp expands macros during 
evaluation, and when you call EVAL or COMPILE, macros are also expanded 
at runtime. However, you cannot pass macros around as first-class 
objects and APPLY them, at least not in the same way as functions. If 
you wanted to do that the language implementation would need to keep the 
lexical environment information available at runtime.)

> Does anybody have a keyword-style list of useful applications of the 
> macro facilities?

Do you have a keyword-style list of useful applications of functions?


Pascal
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo63nv$9rd$1@news.oberberg.net>
Pascal Costanza wrote:
> 
> When you want to bind to a resource, you usually have to make sure that 
> you also unbind again later on. The standard pattern in many languages, 
> modulo syntactic variations, is this:
> 
> try: bind resource
>      do something
> finally: unbind resource
> 
> [...]
> 
> Now, this is admittedly not an example for a particularly sophisticated 
> protocol. Therefore, one of the usual gut reactions from people who are 
> not used to macros yet is "but I can do this with higher order functions!"

Indeed.

> However, what this example already shows is: The with-bound-resource 
> macro doesn't tell you anything about how it achieves its goals. Yes, 
> the natural way to implement this example is with a HOF, but you could 
> also use a completely different approach. _With macros you can build 
> abstractions that completely hide their implementation details._

I can completely hide implementation details with HOFs, too. At least 
for my personal definition of "completely" - macros might have a 
different idea of that.

> This becomes especially useful as soon as your protocols become more 
> sophisticated, and you need to insert instructions at arbitrary places 
> in the code being passed to a macro, or need to control evaluation of 
> the code being passed in some other details.

Inserting "at arbitrary places" seems rather unmodular to me.
Either the macro would have to know about the code that it's being used 
in, so that it can identify the places where to insert the code.
Or the code using the macro will have to pass information to the macro - 
which, in a HOF context, means that the code using the HOF approach will 
have to pass the code for "before the insertion point" and "after the 
insertion point" as separate parameters, and the HOF would do the 
necessary linkage between the two codes.
I'm not sure that macros offer a significant gain here.

> Because of this high level of expressive power that macros provide, 
> Common Lispers use them regularly even for simple things. You can 
> effectively write domain-specific abstractions that don't leak, and 
> therefore it is justified to use them even for simple protocols.

OK, but the same can be said for HOFs.
The question is: in what ways are macros superior to HOFs to accomplish 
this?

>> Um, well, yes, there is one thing that macros can do: extending syntax 
>> in ways that aren't part of the original language syntax. E.g. 
>> replacing all those parentheses by indentation, or something similar 
>> un-Lispish.
>> (Extending syntax in such ways is a mistake IMHO, but YMMV. Anyway, 
>> I'm more interested in the question if there's any /semantics/ that 
>> can be done via macros but not via compile-time evaluation.)
> 
> Compile-time evaluation is a red herring.

See it this way: Macros are a way to create blocks of code. HOFs that 
return functions do the same: they take a few functions (and possibly 
some value arguments), stick them together, and return the result. If 
the HOF is evaluated at compile time (something that I'd expect if both 
functions and values submitted to the HOF are constant), then you too 
have a mechanism that creates a block of code.
The working point is slightly farther down the pipeline: not at the 
abstract syntax level but at the semantics level (in practice, this 
would be somewhere around "decorated abstract syntax", SSA 
representation, basic blocks, or so).

 > Macros do their job by
> rewriting abstract syntax trees. (Lisp and macros go very well together 
> because in Lisp, you essentially program using a notation that maps 
> directly to an internal syntax tree, nearly without any parsing overhead.)

I agree that macros should work on the abstract syntax tree, not at the 
lexical level like the C/C++ preprocessor.

> Since the syntax tree is usually available at compile time, that's the 
> natural time to let macros do their job. However, in theory it wouldn't 
> be a problem to use macro expansion at runtime.

Hmm... it would be highly unpracticable, I'd think.

>> Does anybody have a keyword-style list of useful applications of the 
>> macro facilities?
> 
> Do you have a keyword-style list of useful applications of functions?

I think you forgot a smiley - at least, that question is entirely silly. 
If you have a real point to make, please make it explicit; I have too 
little time to devote to decoding your intents. (And if you don't want 
to spend time on trivialities, then please understand that I don't, too.)

Regards,
Jo
From: Paul Dietz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <3FA6C70C.2BA96F4D@motorola.com>
> Does anybody have a keyword-style list of useful applications of the
> macro facilities?

Here's an example of a utility that is easy to implement with lisp
macros, but rather more difficult to do without them:

http://www-2.cs.cmu.edu/afs/cs/project/ai-repository/ai/lang/lisp/code/testing/cover/0.html
(described in http://www.merl.com/papers/TR91-04/ )

	Paul
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3llqxi9zf.fsf@javamonkey.com>
Joachim Durchholz <·················@web.de> writes:

> Pascal Costanza wrote:

> > This becomes especially useful as soon as your protocols become
> > more sophisticated, and you need to insert instructions at
> > arbitrary places in the code being passed to a macro, or need to
> > control evaluation of the code being passed in some other details.
> 
> Inserting "at arbitrary places" seems rather unmodular to me.
> Either the macro would have to know about the code that it's being
> used in, so that it can identify the places where to insert the code.
> Or the code using the macro will have to pass information to the macro
> -
> which, in a HOF context, means that the code using the HOF approach
> will have to pass the code for "before the insertion point" and "after
> the insertion point" as separate parameters, and the HOF would do the
> necessary linkage between the two codes.
> I'm not sure that macros offer a significant gain here.

So here's one sort of trivial example of something that demonstrates
one aspect of what Pascall was talking about. I'm not sure how you do
this with HOFs since they don't give you any ability to get at the
code at compile time.

  (defmacro show (form)
    "Trace the evaluation of a form and return its value.
  (Could be made smarter about multiple values.)"
    (let ((form-value (gensym)))
      `(let ((,form-value ,form))
         (format *trace-output* "TRACE>> Evaluating ~s; got ~a~%" ',form ,form-value)
         ,form-value)))

  CL-USER: (show (+ 1 2))
  TRACE>> Evaluating (+ 1 2); got 3
  3
  CL-USER: (defun foo (x) (+ (show (+ 1 x)) (+ 3 4) (show (* 5 (* x 4)))))
  FOO
  CL-USER: (foo 10)
  TRACE>> Evaluating (+ 1 X); got 11
  TRACE>> Evaluating (* 5 (* X 4)); got 200
  218

Now that's pretty trivial. But now we can use SHOW to build something
a bit more complex:

  (defmacro show-calls-to ((&rest names) &body body)
    `(progn
       ,@(loop for form in body
             when (member (first form) names) collect `(show ,form)
             else collect form)))

This macro takes a lis of function names to SHOW and a body of forms.
All the top level forms in the body that contain calls to the named
functions are wrapped in a call to SHOW. A more sophisticated, and
useful, version of this macro would use code walker to find
interesting calls other than at the top level.

  CL-USER: (show-calls-to () (- 3 4) (+ 4 5) (* 6 7))
  42
  CL-USER: (show-calls-to (+) (- 3 4) (+ 4 5) (* 6 7))
  TRACE>> Evaluating (+ 4 5); got 9
  42
  CL-USER: (show-calls-to (+ *) (- 3 4) (+ 4 5) (* 6 7))
  TRACE>> Evaluating (+ 4 5); got 9
  TRACE>> Evaluating (* 6 7); got 42
  42

This is not necessarily a typical use of macros, but it does perhaps
demonstrate how a macro can manipulate the code in its arguments
without any particular "cooperation" from the code being manipulated.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Pascal Costanza
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo67q2$c22$2@newsreader2.netcologne.de>
Peter Seibel wrote:

> This is not necessarily a typical use of macros, but it does perhaps
> demonstrate how a macro can manipulate the code in its arguments
> without any particular "cooperation" from the code being manipulated.

That's a cool example! I was looking for something like this!

Thanks!

Pascal
From: Stephen J. Bevan
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3wuagd8e1.fsf@dino.dnsalias.com>
Peter Seibel <·····@javamonkey.com> writes:
[snip]
> Now that's pretty trivial. But now we can use SHOW to build something
> a bit more complex:
> 
>   (defmacro show-calls-to ((&rest names) &body body)
>     `(progn
>        ,@(loop for form in body
>              when (member (first form) names) collect `(show ,form)
>              else collect form)))
> 
> This macro takes a lis of function names to SHOW and a body of forms.
> All the top level forms in the body that contain calls to the named
> functions are wrapped in a call to SHOW. A more sophisticated, and
> useful, version of this macro would use code walker to find
> interesting calls other than at the top level.
> 
>   CL-USER: (show-calls-to () (- 3 4) (+ 4 5) (* 6 7))
>   42
>   CL-USER: (show-calls-to (+) (- 3 4) (+ 4 5) (* 6 7))
>   TRACE>> Evaluating (+ 4 5); got 9
>   42
>   CL-USER: (show-calls-to (+ *) (- 3 4) (+ 4 5) (* 6 7))
>   TRACE>> Evaluating (+ 4 5); got 9
>   TRACE>> Evaluating (* 6 7); got 42
>   42

Is the above something you find you use with any regularity or would
expect others to use?  I ask because unless other people look at it
and go "Wow, that's something I really want and I can now see how to
get it via macros", then macro examples like the above aren't going to
win anyone over.  For my part, show-calls-to is not something I would
ever envisage using.  I can envisage, and occasionally do use, the
trace functionality found in some implementations that allows the
inputs and output(s) of a specified function to be displayed but that
is rather a different beast (though in some Lisp implementations it
might well be partially implemented using a macro).
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3ptg8em7s.fsf@javamonkey.com>
·······@dino.dnsalias.com (Stephen J. Bevan) writes:

> Peter Seibel <·····@javamonkey.com> writes:
> [snip]
> > Now that's pretty trivial. But now we can use SHOW to build something
> > a bit more complex:
> > 
> >   (defmacro show-calls-to ((&rest names) &body body)
> >     `(progn
> >        ,@(loop for form in body
> >              when (member (first form) names) collect `(show ,form)
> >              else collect form)))
> > 
> > This macro takes a lis of function names to SHOW and a body of forms.
> > All the top level forms in the body that contain calls to the named
> > functions are wrapped in a call to SHOW. A more sophisticated, and
> > useful, version of this macro would use code walker to find
> > interesting calls other than at the top level.
> > 
> >   CL-USER: (show-calls-to () (- 3 4) (+ 4 5) (* 6 7))
> >   42
> >   CL-USER: (show-calls-to (+) (- 3 4) (+ 4 5) (* 6 7))
> >   TRACE>> Evaluating (+ 4 5); got 9
> >   42
> >   CL-USER: (show-calls-to (+ *) (- 3 4) (+ 4 5) (* 6 7))
> >   TRACE>> Evaluating (+ 4 5); got 9
> >   TRACE>> Evaluating (* 6 7); got 42
> >   42
> 
> Is the above something you find you use with any regularity or would
> expect others to use? I ask because unless other people look at it
> and go "Wow, that's something I really want and I can now see how to
> get it via macros", then macro examples like the above aren't going
> to win anyone over.

No, as it stands I don't think show-calls-to all that useful. It was
just a quick hack to show how a macro can analyze the its arguments
and generate new code with some new bit of functionality interleaved.
into the code it was passed without that code having to necessarily be
aware of the macro. I don't even think that's a very typical use of
macros but someone was questioning how such a thing could even be
done.

I'm about ready to give up on trying to evangelize macros on
usenet--if you show a simple macro to demonstrate a point people say:
"That's silly, who'd want to do that?" If you show a macro that allows
some simple code to expand into some complex code people say, "I don't
understand that code it expands into, show me a simpler example."

Hopefully I'll finish my chapters about macros soon and I can just
point people to them. (Which will, of course, happen sooner if I stop
spending so much time on Usenet.)

> For my part, show-calls-to is not something I would ever envisage
> using. I can envisage, and occasionally do use, the trace
> functionality found in some implementations that allows the inputs
> and output(s) of a specified function to be displayed but that is
> rather a different beast (though in some Lisp implementations it
> might well be partially implemented using a macro).

All of them, probably, since the standard (if you're talking about
Common Lisp) specifies that it's a macro. ;-)

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Coby Beck
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo7gsd$16iv$1@otis.netspace.net.au>
"Peter Seibel" <·····@javamonkey.com> wrote in message
···················@javamonkey.com...
> ·······@dino.dnsalias.com (Stephen J. Bevan) writes:
> I'm about ready to give up on trying to evangelize macros on
> usenet--if you show a simple macro to demonstrate a point people say:
> "That's silly, who'd want to do that?" If you show a macro that allows
> some simple code to expand into some complex code people say, "I don't
> understand that code it expands into, show me a simpler example."

Yes, it is always a moving target...

I posted this way way upthread but it only made it to one of the
cross-posted groups so I'll try again:

Here's a nice example from some production code I wrote that is easy to
grok.

The purpose: a socket server excepts a set of specific commands from
clients.  Client commands must be verified as allowed and the arguments
marshalled before applying the appropriate function to the arguments.  I
wanted a clean way to express this and automate the writing of error
catching code.

Usage: define-server-cmd name (method-parameters) constraints code

Sample usage:
(define-server-cmd set-field-sequence ((session morph-configuration-session)
                                        field-list)
    ((listp field-list)
     (remove-if-not #'(lambda (key) (member key *logical-types*))
field-list))
  (with-slots (client source-blueprint state) session
    (setf (field-sequence (source-blueprint session)) field-list)
    (setf state :blueprint-set)
    (send session (write-to-string state))))

The resulting expansion:
(PROGN
  (DEFMETHOD SET-FIELD-SEQUENCE
    ((SESSION MORPH-CONFIGURATION-SESSION) FIELD-LIST)
    (WITH-SLOTS (CLIENT SOURCE-BLUEPRINT STATE)
                SESSION
      (SETF (FIELD-SEQUENCE (SOURCE-BLUEPRINT SESSION))
            FIELD-LIST)
      (SETF STATE :BLUEPRINT-SET)
      (SEND SESSION (WRITE-TO-STRING STATE))))
  (DEFMETHOD MARSHAL-ARGS-FOR-CMD
    ((CMD (EQL 'SET-FIELD-SEQUENCE))
     (SESSION MORPH-CONFIGURATION-SESSION))
    (LET (FIELD-LIST)
      (PROGN
        (SETF FIELD-LIST
              (RECEIVE SESSION :TIMEOUT *COMMAND-PARAMETER-TIMEOUT*))
        (UNLESS FIELD-LIST
          (ERROR 'TIMEOUT-ERROR
                 :EXPECTATION
                 (FORMAT NIL "~A parameter to ~A command" 'FIELD-LIST CMD)
                 :TIMEOUT
                 *COMMAND-PARAMETER-TIMEOUT*)))
      (UNLESS (LISTP FIELD-LIST)
        (ERROR 'COMMAND-CONSTRAINT-VIOLATION
               :CONSTRAINT
               '(LISTP FIELD-LIST)
               :COMMAND
               CMD))
      (UNLESS (REMOVE-IF-NOT #'(LAMBDA (KEY)
                                 (MEMBER KEY *LOGICAL-TYPES*))
                             FIELD-LIST)
        (ERROR 'COMMAND-CONSTRAINT-VIOLATION
               :CONSTRAINT
               '(REMOVE-IF-NOT #'(LAMBDA (KEY)
                                   (MEMBER KEY *LOGICAL-TYPES*))
                               FIELD-LIST)
               :COMMAND
               CMD))
      (LIST FIELD-LIST)))
  (PUSHNEW 'SET-FIELD-SEQUENCE *CONFIG-SERVER-COMMANDS*))

Usage of what the macro gave me in context (some error handling noise
removed):

(defmethod run-config-command-loop ((session morph-configuration-session))
  (let ((*package* (find-package :udt)))
  (unwind-protect
      (with-slots (client) session
        (loop
         (let (cmd)
           (setf cmd (receive session :timeout *command-timeout*
                                      :eof-value :eof))
               (cond
                ((or (eq cmd :eof) (eq cmd :stop)) (return))
                ((member cmd *config-server-commands*)
                 (let ((cmd-args (marshal-args-for-cmd cmd session)))
                   (apply cmd session cmd-args)))
                (t (execute-generic-command cmd client)))))

        (send session "session loop terminated"))
    (when (eq (state session) :finalized)
        (setf *active-sessions* (delete session *active-sessions*))))))

The macro definition:

(defmacro define-server-cmd (name (session-specializer &rest args)
     constraints &body body)
  (let ((session-var (car session-specializer))
        (session-class (cadr session-specializer)))
    `(progn
       (defmethod ,name ((,session-var ,session-class)
          ,@(mapcar #'(lambda (arg)
   (if (symbolp arg) arg (car arg)))
      args))
  ,@body)
       (defmethod marshal-args-for-cmd
           ((cmd (eql ',name)) ,session-specializer)
         (let (,@args)
           ,@(loop for var in args
                   collect
     `(progn
        (setf ,var (receive ,session-var
       :timeout *command-parameter-timeout*))
        (unless ,var
   (error 'timeout-error
          :expectation (format nil "~A parameter to ~A command"
                               ',var cmd)
          :timeout *command-parameter-timeout*))))
           ,@(loop for con in constraints
                   collect
     `(unless ,con
        (error 'command-constraint-violation
        :constraint ',con
        :command cmd)))
           (list ,@args)))
       (pushnew ',name *config-server-commands*))))

I think the advantages are tremendously obvious, and very satisfying to make
use of!

-- 
Coby Beck
(remove #\Space "coby 101 @ big pond . com")
From: Espen Vestre
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <kwsml4v7gp.fsf@merced.netfonds.no>
"Coby Beck" <·····@mercury.bc.ca> writes:

> The purpose: a socket server excepts a set of specific commands from
> clients.  Client commands must be verified as allowed and the arguments
> marshalled before applying the appropriate function to the arguments.  I
> wanted a clean way to express this and automate the writing of error
> catching code.
> 
> Usage: define-server-cmd name (method-parameters) constraints code

AOL! I have almost the same thing myself, except that my macro does
less, it just registers the code in a hash table and lets other code
do the rest of the work.

-- 
  (espen)
From: Stephen J. Bevan
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3sml3cjtf.fsf@dino.dnsalias.com>
"Coby Beck" <·····@mercury.bc.ca> writes:
> Here's a nice example from some production code I wrote that is easy to
> grok.

I follow it to a certain extent but the problem now is that we are
given a solution with together with an explanation of what it does,
but we don't know all the details of the problem that shaped the
solution.  Therefore while it is possible to agree that the macro
version obviously hides a lot of detail, it isn't entirely clear if
that is the best way to hide it or even if that detail is required.

I'm not asking you to give the full requirements for your program,
only explaining why if it isn't clear what the problem is then nobody
can easily tell if the macro-based solution is an improvement over
anything else.  For example, if the commands have any kind of grammar
then solution is to define the grammar and let a parser generator take
care of parsing and building an AST.  Whether the parser generator is
an extension of the language (as is possible in Lisp and Forth) or a
separate language (most other languages) is to a certain extent an
implementation detail.  At the other extreme is a simple flat file
that is processed by an AWK program to generate source in the target
language.  To someone used to using macros, the AWK approach looks
like a really poor substitute for a subset of what macros can do and
it is from that perspective.  However, the AWK route is also an
approach that can solve a lot of simple problems, probably even the
one you solved using macros.  Note I'm not going to argue that it any
solution using AWK is *better* than using a macro based solution, only
that to sell macros to someone using the AWK approach the pitch has to
convince them that the macro approach is significantly better in
order to be worth investing the time and effort to learn.  What
constitues "significant" obviously varies.
From: Bruce Lewis
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <nm9d6c6n1fv.fsf@scrubbing-bubbles.mit.edu>
·······@dino.dnsalias.com (Stephen J. Bevan) writes:

> I'm not asking you to give the full requirements for your program,
> only explaining why if it isn't clear what the problem is then nobody
> can easily tell if the macro-based solution is an improvement over
> anything else.

I have to get back to class soon, but here's a quick rundown of two
macros in BRL (http://brl.sourceforge.net/) and why I think they're
nicer than HOFs for the same purpose:

In ASP/VBScript you might do something like

a=request("a")
b=request("b")
c=request("c")

A BRL macro makes it simply:

(define-input a b c)

Half as many opportunities for typos, as you can both use the name of
the variable and bind the variable.

BRL also has a sql-repeat macro.  Within it is some syntax, e.g.
(group-ending? expr)

Here, expr is any expression where the free variables are bound to data
columns returned from an SQL query.  It returns true if you're at the
end of the results, or if expr will be different for the next row.  This
kind of predicate turns eager evaluation on its ear, but lazy evaluation
won't give it to you either.  You can do it with HOFs, but not so
concisely.  As this is a simple, intuitive mental concept, the
conciseness is nice.

That's all for now.  Class is starting.
From: Kenny Tilton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <Oe7qb.62360$ri.10310623@twister.nyc.rr.com>
Stephen J. Bevan wrote:
> "Coby Beck" <·····@mercury.bc.ca> writes:
> 
>>Here's a nice example from some production code I wrote that is easy to
>>grok.
> 
> 
...

> anything else.  For example, if the commands have any kind of grammar
> then solution is to define the grammar and let a parser generator take
> care of parsing and building an AST.  Whether the parser generator is
> an extension of the language (as is possible in Lisp and Forth) or a
> separate language (most other languages) is to a certain extent an
> implementation detail.

No, this misses the whole point. The idea precisely is not to have to 
jump out of the IDE, move to external tool X that has none of the 
knowledge available to code within the application, define a grammar 
which must now be kept in synch with new decisions made back in the HLL 
IDE (that is always /so/ much fun) to generate transformed code which 
must be regenerated in its entirety anytime the grammar changes.

That is like saying I do not need OO because I can have a type slot and 
all my code can dispatch off that, so there is my OO.

The world gets better when something you can do the hard way (and using 
AWK instead of macros really takes the cake on that score) gets 
supported by a polished language mechanism.

To a large degree, all these Turing-equivalent non-repsonses are doing a 
good job of explaining why macros are useful: who needs a jet to get 
from NYC to Beijing? C'mon, Amtrak, kayak, Great Wall...good morning, 
Beijing!

kenny

-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Stephen J. Bevan
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3oevqdg5q.fsf@dino.dnsalias.com>
Kenny Tilton <·······@nyc.rr.com> writes:
> > anything else.  For example, if the commands have any kind of grammar
> > then solution is to define the grammar and let a parser generator take
> > care of parsing and building an AST.  Whether the parser generator is
> > an extension of the language (as is possible in Lisp and Forth) or a
> > separate language (most other languages) is to a certain extent an
> > implementation detail.
> 
> No, this misses the whole point. The idea precisely is not to have to
> jump out of the IDE, move to external tool X that has none of the
> knowledge available to code within the application, define a grammar
> which must now be kept in synch with new decisions made back in the
> HLL IDE (that is always /so/ much fun) to generate transformed code
> which must be regenerated in its entirety anytime the grammar changes.

As I noted in the section you snipped, an AWK-like solution looks
pretty poor to someone used to using Lisp style macros.  However, lots
of people take the AWK-like approach because it works for them with
whatever language they are currently using.  Simply telling them it is
a poor way to work is not going to win them over to macros.  Showing
them examples of how macros simplfy a given problem in Common Lisp are
useful but can still fall flat if they can't identify with that
problem.  What they want to see is either a Common Lisp (with macros)
solution to their problem or an example of a known problem with a
solution recast in Common Lisp utilising macros.  That obviously
pushes a lot of effort on those who want to make the case for macros.


> That is like saying I do not need OO because I can have a type slot
> and all my code can dispatch off that, so there is my OO.

I don't think it is like saying that at all, but rather than digress
let's just try and avoid similies or analogies altogether.


> The world gets better when something you can do the hard way (and
> using AWK instead of macros really takes the cake on that score) gets
> supported by a polished language mechanism.
> 
> To a large degree, all these Turing-equivalent non-repsonses are doing
> a good job of explaining why macros are useful: who needs a jet to get
> from NYC to Beijing? C'mon, Amtrak, kayak, Great Wall...good morning,
> Beijing!

Telling people that they are producing "Turing-equivalent
non-responses" isn't going to win them over either.
From: Kenny Tilton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <uR8qb.62367$ri.10343173@twister.nyc.rr.com>
Stephen J. Bevan wrote:

 >  However, lots
 > of people take the AWK-like approach because it works for them with
 > whatever language they are currently using.

But the question is "why macros?" Answer, so you do not have to use Awk.

Now you are in some fantasy-land where someone addresses a domain by 
creating a domain-specific langugae under Awk, then generates all their 
Java, Perl, Python, Ruby, PHP, and STP code from that. Cool! Is that in 
Matrix 4?

That was not an analogy, btw. I was already using the C switch statement 
to dispatch off an explicit "type" slot in C structs to achieve (what?) 
polymorphism when I heard about Smalltalk. I did not think "I already 
have that, however crappy and tedious to deal with when I come up with a 
new type". I thought, "Brilliant. Somebody thought to build that into a 
language."

But then I am not afraid to learn new languages.

kenny

-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Stephen J. Bevan
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3k76ecjj3.fsf@dino.dnsalias.com>
Kenny Tilton <·······@nyc.rr.com> writes:
> Stephen J. Bevan wrote:
>  >  However, lots
>  > of people take the AWK-like approach because it works for them with
>  > whatever language they are currently using.
> 
> But the question is "why macros?" Answer, so you do not have to use Awk.

That seems to be the question you want to answer, but I don't think it
is the question others are really asking based on the fact that the CL
macro examples haven't obviously won many over.  I explained in the
message to which you responded one approach that can be taken in order
to sell macros more effectively IMHO.  I have no desire to debate the
merits of that approach, people can use it or ignore it as they see fit.
From: Kenny Tilton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <%Tjqb.62665$ri.10658467@twister.nyc.rr.com>
Stephen J. Bevan wrote:
> Kenny Tilton <·······@nyc.rr.com> writes:
> 
>>Stephen J. Bevan wrote:
>> >  However, lots
>> > of people take the AWK-like approach because it works for them with
>> > whatever language they are currently using.
>>
>>But the question is "why macros?" Answer, so you do not have to use Awk.
> 
> 
> That seems to be the question you want to answer, but I don't think it
> is the question others are really asking based on the fact that the CL
> macro examples haven't obviously won many over. 

<heh-heh> The stuff I write in response to macro-resistant argumentation 
is not for the arguers, it is for lurkers who might actually be thinking 
while they are reading. jeez, Paul Graham wrote a whole book on macros, 
lispniks swear by macros. That's all it takes to get "I am Curious 
(language)" types to get interested.

NG arguers are just NG arguers.

Here's a real-live working macro I used last week:

(defmodel ring-net (family)
   (
    (ring-ids :cell nil :initform nil
	:accessor ring-ids :initarg :ring-ids)
    (sys-id :cell nil :initform nil :accessor sys-id :initarg :sys-id)
    (reachable-nodes :initarg :reachable-nodes :accessor reachable-nodes
       :initform (c? (let (reachables)
                       (map-routers-up
                           (lambda (node visited)
                              (declare (ignore visited))
                              (push node reachables))
                           (find (sys-id self) (^kids)
                              :key 'md-name))
                        reachables)))
    (clock :initform (cv 0) :accessor clock :initarg clock)
    ))

DEFMODEL wraps DEFCLASS, itself a macro. Let's expand the above:

<<<BEGIN>>>>>
(progn (eval-when (:compile-toplevel :execute :load-toplevel)
          (setf (get 'ring-net :cell-defs) nil))
        nil nil
        (eval-when (:compile-toplevel :execute :load-toplevel)
          (setf (md-slot-cell-type 'ring-net 'reachable-nodes) t)
          (unless (macro-function '^reachable-nodes)
            (defmacro ^reachable-nodes (&optional (model 'self) synfactory)
              (excl::bq-list `let (excl::bq-list (excl::bq-list 
`*synapse-factory* synfactory))
                             (excl::bq-list 'reachable-nodes model)))))
        (eval-when (:compile-toplevel :execute :load-toplevel)
          (setf (md-slot-cell-type 'ring-net 'clock) t)
          (unless (macro-function '^clock)
            (defmacro ^clock (&optional (model 'self) synfactory)
              (excl::bq-list `let (excl::bq-list (excl::bq-list 
`*synapse-factory* synfactory))
                             (excl::bq-list 'clock model)))))
        (progn (defclass ring-net (family)
                         ((ring-ids :initform nil :accessor ring-ids 
:initarg :ring-ids)
                          (sys-id :initform nil :accessor sys-id 
:initarg :sys-id)
                          (reachable-nodes :initarg :reachable-nodes 
:accessor reachable-nodes
                                           :initform
                                           (c? (let (reachables)
                                                 (map-routers-up (lambda
                                                                  (node 
visited)
 
(declare (ignore visited))
                                                                  (push 
node reachables))
                                                                 (find

 
(sys-id self)
                                                                  (^kids)

                                                                  :key
                                                                  'md-name))
                                                 reachables)))
                          (clock :initform (cv 0) :accessor clock 
:initarg clock))
                         (:documentation "chya") (:default-initargs) 
(:metaclass standard-class))
               (defmethod shared-initialize :after ((self ring-net) 
slot-names &rest iargs)
                 (declare (ignore slot-names iargs))
                 (unless (typep self 'model-object)
                   (error "if no superclass of ~a inherits directly
or indirectly from model-object, model-object must be included as a 
direct super-class in
the defmodel form for ~a" 'ring-net 'ring-net)))
               nil nil
               (progn (defmethod reachable-nodes ((self ring-net))
                        (md-slot-value self 'reachable-nodes))
                      (defmethod (setf reachable-nodes) (new-value (self 
ring-net))
                        (setf (md-slot-value self 'reachable-nodes) 
new-value))
                      nil)
               (progn (defmethod clock ((self ring-net)) (md-slot-value 
self 'clock))
                      (defmethod (setf clock) (new-value (self ring-net))
                        (setf (md-slot-value self 'clock) new-value))
                      nil)
               (find-class 'ring-net)))

<<<END>>>>

Oh, I'm sorry, did I fill up your hard drive? Were you looking forward 
to typing all that by hand? And revisiting a hundred or so like that 
when you decided to change what DEFMODEL does?

That is point #1.

Point #2: some but not all of the above went away when I did a version 
using a metaclass. But then I wanted to open source the hack, and not 
all Lisps do the MOP. The point being that in general one can get very 
cool semantics absent cool built-in language stuff precisely because 
sufficient plumbing can achieve most cool effects, and macros let one 
hide all that plumbing. This point will be too subtle for many, whow 
might yell out "But my language has a MOP and there is only one imp". I 
am making a more general point: macros mean one is not limited by ones 
chosen language.

Point #3: DEFMODEL is part of a VLH (Very Large Hack). Now you might 
say, "I don't do Very Large Hacks!". Well, maybe you do, but maybe you 
just ahve a lot of function calls all over with a lot of redundant, 
boilerplate code arranged Just So to conform to the requirements of the 
hack. With macros the boilerplate disappears (and again) you thank your 
lucky stars when you make a neat improvement to the VLH and you do not 
need to revisit all the boilerplate.

Now let's look in one level, to:

   (c? (let (reachables)
         (map-routers-up (lambda (node visited)
                            (declare (ignore visited))
                            (push node reachables))
                         (find (sys-id self) (^kids)
                             :key 'md-name))
                         reachables))

and expand that:

   (MAKE-C-DEPENDENT
       :CODE '((LET (REACHABLES)
                  (MAP-ROUTERS-UP (LAMBDA (NODE VISITED)
                               (DECLARE (IGNORE VISITED))
                               (PUSH NODE REACHABLES))
                             (FIND (SYS-ID SELF) (^KIDS) :KEY 'MD-NAME))
              REACHABLES))
       :RULE (C-LAMBDA (LET (REACHABLES)
                        (MAP-ROUTERS-UP (LAMBDA (NODE VISITED)
                                           (DECLARE (IGNORE VISITED))
                                           (PUSH NODE REACHABLES))
                                        (FIND (SYS-ID SELF) (^KIDS)
                                           :KEY 'MD-NAME))
                                        REACHABLES)))

That exaggerates things a little, because that code keyword is receiving 
at runtime the /source/ of the form expanded into the code to be 
compiled as an anonymous function, so I can figure out what code crashed 
when I end up in a backtrace. Sorry if I scared the children with that one.

Now don't feel bad if you don't recognize C-LAMBDA, that's mine:

   (LAMBDA (#:G1000 &AUX (SELF (C-MODEL #:G1000))
             (.CACHE (C-VALUE #:G1000)))
        (DECLARE (IGNORABLE .CACHE SELF))
        (ASSERT (NOT (CMDEAD #:G1000)) NIL
              "cell dead entering rule ~a" #:G1000)
     (LET (REACHABLES)
       (MAP-ROUTERS-UP (LAMBDA (NODE VISITED)
                          (DECLARE (IGNORE VISITED))
                          (PUSH NODE REACHABLES))
                       (FIND (SYS-ID SELF) (^KIDS)
                           :KEY 'MD-NAME))
                       REACHABLES))

Still there? OK, this VLH has many different kinds of macros such as C?, 
but they all get called in exactly one place. They need the same lambda 
signature. Before I had C-LAMBDA, a rare change to that signature was a 
real pain. No mas.

OK, by now I am sure you are fascinated by: (^kids)

Expanded, we get: (KIDS SELF)

Beezlebub! Don't worry, it compiles. The ^thingy macros are meant to be 
invoked only in lexical contexts supplying the Smalltalk-like ubiquitous 
anaphor SELF. look back at the expansion of c-lambda to see SELF being 
pulled out of the model slot of the cell. ie, big bad variable capture 
has been harnessed for a good cause, emulating the anaphoric variables 
of SELF and THIS of other languages. I scared a grown-up Lispnik with 
this, once.

^these used to do even more work, but an improvement made them (almost) 
unnecessary, but I kept them because I need them for the following and 
because I kinda dig the way they shout out "I am using one of my own 
slots!".

POINT #4: Sometimes macros just brighten up the code a little.

Where they are still needed is:

      code: (^clock system (fSensitivity 30))
expansion: (LET ((*SYNAPSE-FACTORY* (FSENSITIVITY 30)))
               (CLOCK SYSTEM))

whoa! where did all that come from? the macro decided to write a little 
more code when it saw me using the synapse option. Now the important 
thing here is that *SYNAPSE_FACTORY* gets picked up in the access done 
by (clock system), so ya can't do a high-level function:

     (func-to-apply-synapse (FSensitivity 30) (clock system))

and you can't pass it to the clock function because that is an accessor 
and good CLOSians don't fuck with accessor signatures.

in fact whatever trick you come up with would be uglier than:

     (LET ((*SYNAPSE-FACTORY* (FSENSITIVITY 30)))
               (CLOCK SYSTEM))

So yer stuck with it. Not me, tho.

POINT #5: Sometimes macros brighten up the code /and/ hide necessary 
plumbing.

Now getting back to the VLH issue, all the above is about taking 
something developers do in any language from 6502 to Lisp, viz, create 
little code worlds in which functions and variables and stuff are 
regularly used repeatedly many times, and allowing one's implementation 
to seemingly expand to include the new custom code world, hiding a lot 
of boilerplate in the process.

Now I know what you are going to say. No one will buy any of that 
because they have no fucking idea what I am talking about. Ah, but they 
can tell I am having a /lot/ of fun, and <cue Burdick> if you check the 
highlight film below, you'll find a whole section on Hedonists.

kenny



-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Coby Beck
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bockm9$1pqk$1@otis.netspace.net.au>
"Stephen J. Bevan" <·······@dino.dnsalias.com> wrote in message
···················@dino.dnsalias.com...
> "Coby Beck" <·····@mercury.bc.ca> writes:
> > Here's a nice example from some production code I wrote that is easy to
> > grok.
>
> I follow it to a certain extent but the problem now is that we are
> given a solution with together with an explanation of what it does,
> but we don't know all the details of the problem that shaped the
> solution.  Therefore while it is possible to agree that the macro
> version obviously hides a lot of detail, it isn't entirely clear if
> that is the best way to hide it or even if that detail is required.

The problem was a fairly ordinary one and is easy to describe at a high
level.  The server existed to control a complicated configuration process
and later process data according to the result.  It was a simple socket
server and I got to dictate the form of the commands and arguments.
Ultimately, it boiled down to (funcall command client-session args).

So I needed (wanted) a way to, in one stroke,
- define the method, properly specialized on the session object
- ensure it became an allowed function to call
- define a way to gather the arguments needed from the client
  according to number of args and the type of each.
- provide a facility for arbitrarily complex validation of any
  of the arguments or combinations thereof.
- ensure that any changes, enhancements or additions to
  argument passing would require a single point of change in my code.

Additional benefits:
- automatically provided information to a kind of "help" facility.
- allowed for very informative error messages, both in the debug
  environment and as returned data for clients.
- simplified the main server loop while remaining completely flexible

> I'm not asking you to give the full requirements for your program,
> only explaining why if it isn't clear what the problem is then nobody
> can easily tell if the macro-based solution is an improvement over
> anything else.

Hopefully the above is enough of a spec.  I would be very happy to learn
other approaches, there are always many ways to skin a cat. (how un-PC is
that saying these days ;)

>  For example, if the commands have any kind of grammar
> then solution is to define the grammar and let a parser generator take
> care of parsing and building an AST.

I was fortunate to be the one defining the API so I came up with a very
clever way of having named and optional arguments that could be atoms or
lists defined by ( and ) characters.  (I should patent that ;)

I did have to define a set of safe-read functions for lists and integers and
strings etc for a combination of security and timing-out reasons.  But the
grammar was just s-expressions.  (It was culture shock for the Java client
coders, and I think they still would say SOAP was better though it is beyond
me why).

>  Whether the parser generator is
> an extension of the language (as is possible in Lisp and Forth) or a
> separate language (most other languages) is to a certain extent an
> implementation detail.  At the other extreme is a simple flat file
> that is processed by an AWK program to generate source in the target
> language.  To someone used to using macros, the AWK approach looks
> like a really poor substitute for a subset of what macros can do and
> it is from that perspective.

If the target language is Lisp, then not "looks like", but "is".  I think
you know that, though.  I actually have macros I use now that generate
strings of SQL code, some of it as format strings that will be used at a
later stage of processing (a "format string" would be something like "SELECT
NEW.~A FROM ~A WHERE ~A > 3" where the ~A's get filled with variables later)

>  However, the AWK route is also an
> approach that can solve a lot of simple problems, probably even the
> one you solved using macros.  Note I'm not going to argue that it any
> solution using AWK is *better* than using a macro based solution, only
> that to sell macros to someone using the AWK approach the pitch has to
> convince them that the macro approach is significantly better in
> order to be worth investing the time and effort to learn.  What
> constitues "significant" obviously varies.

This trade-off is not unique to macros, it is what we all face all the time
with new and maybe better tools or approaches.  The start-up cost makes the
first uses too expensive.  I don't know AWK at all, I'm sure if I did I
would not just open that file in emacs and use a few keyboard macros as
often...

"By the time I walk to the shed and get the socket wrench, I'll have already
got this nut off with the vice-grips..."  And it's true!  The problem being
that then at nut number five I'm thinking "if I had just gone to get that
socket wrench in the beginning, this next nut would already be off"  I have
to confess I am guilty of that all the time....But I try not to kid myself
that vice-grips are generally the best tool for removing nuts and bolts.

But back to macros, and really any language feature, they are all just tools
and it is always a judgment call as to what the best tool for a job is and
judgements are always subjective.  It is very hard to convince anyone that a
tool they are completely unfamiliar with is the best one for some problem
they never thought they had.

-- 
Coby Beck
(remove #\Space "coby 101 @ big pond . com")
From: Dirk Thierbach
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <l94q71-n65.ln1@ID-7776.user.dfncis.de>
Coby Beck <·····@mercury.bc.ca> wrote:
> The problem was a fairly ordinary one and is easy to describe at a high
> level.  The server existed to control a complicated configuration process
> and later process data according to the result.  It was a simple socket
> server and I got to dictate the form of the commands and arguments.
> Ultimately, it boiled down to (funcall command client-session args).

> I would be very happy to learn other approaches, there are always
> many ways to skin a cat. (how un-PC is that saying these days ;)

Here's a very simplified example how to do something similar in
Haskell. I probably missed lots of details (I don't know how the
session object works, and have no idea what the session-blueprints
are, I have no details about the send and receive commands, and so on),
but maybe it should give you an idea.

The main task is to define a function that implements a server
command, given some constraints and the code for the command.
The command should work on the arguments received over the socket.

So we need some code that does the marshalling und un-marshalling of
the data. Here, I will cheat and just use the "Dynamic" library
to simulate that. In reality, one could use a similar approach
to write marshalling routines, or use the standard read and show
routines, or whatever. I'll use the functions

toDyn :: Typeable a => a -> Dynamic

that converts any "typeable" value into a Dynamic value, and

fromDynamic :: Typeable a => Dynamic -> Maybe a

which converts it back, or fails with a value of "Nothing" if the type
doesn't match. The class Typeable will need instances for all the
types we want to convert.

Let's assume there is a type "Session" for sessions. Then the type
of define_server_cmd will be

define_server_cmd :: Typeable a => (a -> Bool) -> (Session -> a -> IO ()) 
  -> (Session -> Dynamic -> IO ())

which pretty much expresses out expectations about this function given
above. The implementation is straightforward:

define_server_cmd constraints code session dyn_args = do
  maybe 
    (error "Wrong type of arguments") 
    (\args -> if constraints args 
       then code session args 
       else error "Constraints violated"  
    )
    (fromDynamic dyn_args)  

Your set-field-sequence example would probably look something like
(I am guessing a lot here)

set_field_sequence = define_server_cmd constraints code where
  constraints field_list = all (`elem` logical_types) field_list
  code session field_list = do
    let field_sequence = source_blueprint session
        state          = get_state session
    writeIORef field_sequence field_list
    send session (show state)

You don't need the first constraint, because the unmarshalling will
check if the arguments are indeed a list. I am not sure if the
second constraint is also a type check or if it checks the contents
or names of the fields.

As another example, let's define the code for a print command
seperately (so it is testable), and then make a server command out
of it with the constraint that the first argument is less then 100:

print_cmd_code :: Session -> (Integer, String) -> IO ()
print_cmd_code session (x, y) = 
  print ("First=" ++ show x ++ ", Second=" ++ show y)

print_cmd = define_server_cmd (\(x, _) -> x < 100) print_cmd_code 


As I said, this is a very simple example, so let's see what is missing.

> So I needed (wanted) a way to, in one stroke,
> - define the method, properly specialized on the session object
Should work.

> - ensure it became an allowed function to call
Should work.

> - define a way to gather the arguments needed from the client
>  according to number of args and the type of each.
Should work. Note that the compiler automatically figures out at
compile time which code to combinbe to marshall or unmarshall the 
"dynamic" value, and verifies the type as well. No need to do this
explicitely.

> - provide a facility for arbitrarily complex validation of any
>  of the arguments or combinations thereof.
Should work.

> - ensure that any changes, enhancements or additions to
>  argument passing would require a single point of change in my code.
Should work.

One potential drawback of the above approach is that you have to write
down the argument list twice, once for the contraint check, and once
for the actual code. But since one might want to do pattern matching
on the arguments, this might be exactly the right thing and not a
drawback. The type checker will verify that the arguments are of the
same for both parts.

> Additional benefits:
> - automatically provided information to a kind of "help" facility.
I didn't see that in your code, but one could probably handle this
in the same ways as errors below.

> - allowed for very informative error messages, both in the debug
>  environment and as returned data for clients.

I kept the error handling *very* simple by just throwing exceptions.
In reality, this would be handled by an error function that sends back
the error message. Type errors could be automatically handled. It is
of course not possible to send back sourc code as a string without
using a macro; and while error messages of this kind are arguably
informative to someone who knows lisp, they might be very confusing to
someone who doesn't :-) So I'd add explicit error messages, and maybe
a few infix functions as syntactic sugar to write them down nicely.

> - simplified the main server loop while remaining completely flexible
The main loop would need to lookup the server functions (which all
have the same type), and then execute the functions without
unmarshalling the arguments, since that is done inside the
function. Also simple and flexible.


> I did have to define a set of safe-read functions for lists and
> integers and strings etc for a combination of security and
> timing-out reasons.

Yes. This code would go in the typeclasses mentioned at the beginning,
and as you say, you'd need that in Lisp, too.

> But the grammar was just s-expressions.  
The grammar is completely up to the coder, be it s-expressions, XML, or
whatever. However, it should include the type of the arguments passed
over the socket.

> I actually have macros I use now that generate strings of SQL code,
> some of it as format strings that will be used at a later stage of
> processing (a "format string" would be something like "SELECT NEW.~A
> FROM ~A WHERE ~A > 3" where the ~A's get filled with variables
> later)

It might be interesting for you to have a look at HaXML or one of the
other XML libraries that do a similar thing with XML, using only
HOFs. I don't see any reason why SQL couldn't be handled in a similar way.

> But back to macros, and really any language feature, they are all
> just tools and it is always a judgment call as to what the best tool
> for a job is and judgements are always subjective. It is very hard
> to convince anyone that a tool they are completely unfamiliar with
> is the best one for some problem they never thought they had.

Amen to that.

- Dirk
From: Stephen J. Bevan
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3brrodit0.fsf@dino.dnsalias.com>
"Coby Beck" <·····@mercury.bc.ca> writes:
[big snip]
> But back to macros, and really any language feature, they are all just tools
> and it is always a judgment call as to what the best tool for a job is and
> judgements are always subjective.  It is very hard to convince anyone that a
> tool they are completely unfamiliar with is the best one for some problem
> they never thought they had.

Indeed.  That's why I suggested if one wants to convince someone of
the utility of macros one has to find out what problems they are
trying to solve and show how macros can help them solve those
problems (obviously takes time and effort).  Attempts to show the
utility of macros by showing how one solves one's own problems using
them tend to miss the mark unless one is lucky and others are trying
to solve the same problems.
From: Pascal Costanza
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo67dt$c22$1@newsreader2.netcologne.de>
Joachim Durchholz wrote:

>> This becomes especially useful as soon as your protocols become more 
>> sophisticated, and you need to insert instructions at arbitrary places 
>> in the code being passed to a macro, or need to control evaluation of 
>> the code being passed in some other details.
> 
> Inserting "at arbitrary places" seems rather unmodular to me.
> Either the macro would have to know about the code that it's being used 
> in, so that it can identify the places where to insert the code.
> Or the code using the macro will have to pass information to the macro - 
> which, in a HOF context, means that the code using the HOF approach will 
> have to pass the code for "before the insertion point" and "after the 
> insertion point" as separate parameters, and the HOF would do the 
> necessary linkage between the two codes.
> I'm not sure that macros offer a significant gain here.

a) "insert instructions at arbitrary places in the code being passed to 
a macro" means that the macro modifies the code that is being passed to 
it - not the code that surrounds the use site of a macro.

b) For macros, you don't have to partition the information the macro 
needs to do its job into several parameters. A macro just analyzes the 
code that is being passed to it, and automagically does the right thing. 
;) (This is part of the reason why macros allow you to build 
abstractions that don't leak: you don't have to arrange the parameters 
for the macro according to the implementation details of the macro, but 
in more or less completely arbitrary ways.)

c) The significant gain of macros is this: Macros rewrite syntax trees, 
and you can implement any language feature, domain-specific or not, via 
syntax tree rewriting. This means that, no matter what happens during 
software development, you can always find a way to express things in a 
convenient way.

This is mainly a psychological effect: macros greatly reduce the need to 
plan ahead and allow for experimenting with program designs: Just write 
down the code as you imagine to be suitable for the concrete problem at 
hand, and then start to implement it from there. It's very likely that 
you will find out how to implement the machinery beneath in that process 
and then write a bunch of macros that translate your original ideas on 
top of that machinery. You don't have to plan ahead what the "right" 
design is for you problem.

Switch from FP to OOP later on? No problem: rewrite the machinery, 
reimplement your macros, don't change the high-level code. Oops, your 
field should have been methods, or externally stored in a database? No 
problem: rewrite the machinery, reimplement your macros, don't change 
the high-level code.

Without macros, it's very likely that in these cases, when you have to 
change the design of your libraries, you also have to change client 
code. With macros, you don't have to. At least not in 99% of the cases. ;-P

>> Because of this high level of expressive power that macros provide, 
>> Common Lispers use them regularly even for simple things. You can 
>> effectively write domain-specific abstractions that don't leak, and 
>> therefore it is justified to use them even for simple protocols.
> 
> OK, but the same can be said for HOFs.
> The question is: in what ways are macros superior to HOFs to accomplish 
> this?

Most importantly: HOFs as such are rarely domain-specific. So whenever 
your library requires you to express a piece of code with an anonymous 
function, you give away details about the implementation of a specific 
feature.

> See it this way: Macros are a way to create blocks of code. HOFs that 
> return functions do the same: they take a few functions (and possibly 
> some value arguments), stick them together, and return the result. If 
> the HOF is evaluated at compile time (something that I'd expect if both 
> functions and values submitted to the HOF are constant), then you too 
> have a mechanism that creates a block of code.

I don't care about blocks of code or compile-time evaluation, at least 
not most of the time. When I see this...


(with-open-file (stream filename
                  :direction :output
                  :if-does-not-exist :create)
   (format stream "some output"))


...I see a piece of code that tells the machine to open a file in a 
specified way, write some output to it and then closes it gracefully. I 
don't care whether this is achieved by means of OOP abstraction, HOFs, 
or whatever. Such code "talks" only about the necessary details and 
nothing else.

>>> Does anybody have a keyword-style list of useful applications of the 
>>> macro facilities?
>>
>>
>> Do you have a keyword-style list of useful applications of functions?
> 
> 
> I think you forgot a smiley - at least, that question is entirely silly. 
> If you have a real point to make, please make it explicit; I have too 
> little time to devote to decoding your intents. (And if you don't want 
> to spend time on trivialities, then please understand that I don't, too.)

Your question is as silly as mine. ;)

If you want to get an idea what you can do with macros, Paul Graham 
provides an excellent overview in his book "On Lisp" that you can 
download for free at http://www.paulgraham.com/onlisp.html


Pascal
From: Rene de Visser
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo63ci$2m9$1@news1.wdf.sap-ag.de>
"Joachim Durchholz" <·················@web.de> wrote in message
·················@news.oberberg.net...
>
> Does anybody have a keyword-style list of useful applications of the
> macro facilities?
>
I don't write macros that often, I mainly use HOF's.

I always think of a macro as a function that takes some code and returns
some code, and takes place at compile time.

I think that macro's can be categorized as follows:

1) Create new bindings (variable for function bindings).

One of the simplest macros that I use is mvlet* (for multiple value
bindings). This lets you do things like

(mvlet ((
    (c (func1 d)
    (:values a b) (func2 e))
    ...
which binds a b to the values returned by func2. Due to an accident of fate
multiple values aren't so well integrated into common lisp,
so macros can be used to remove deficiencies from langauge.

2) Generating/changing code from meta data.

i)

(with-extracting-expressions (a b c)
   .... )

where a b c are functions that can be assumed to be side-effect free. Based
on this expressions should be bubbled up to the outside
to improve performance.

ii) Removing almost repeated code.

Often I notice that in a program there is code that is similar but not
identical. Then a macro can be written that based on meta data generates the
various different versions of this code.

3) New languages or semantics which expand to lisp code.

e.g. relation lisp, screamer (non-deterministic lisp), parsers, series,
CLOS.

As a side note, I note that in the GHC source code that the parser is
generated Haskell code. Why is not the parser directly specified in Haskell?

In common lisp you would specify the parser directly in LISP and macros
would expand/transform it to its final runable form.

Rene.
From: Alain Picard
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <87he1rdt9d.fsf@memetrics.com>
Joachim Durchholz <·················@web.de> writes:

> Alain Picard wrote:
>
>> More precisely: "macros make control of when, if, and how often,
>>                  something is evaluated _possible_."  Functions
>> (your only other option) give you no choice.
>
> This statement is wrong if left in full generality: higher-order
> functions can control quite precisely what gets evaluated when. If the
> language offers both lazy and strict parameters, evaluation time
> control extends to the parameter expressions as well.

My apologies to the functional guys.  I was responding from a lisp
newsgroup: so let me amend the above to end with "IN LISP".
[We do not have lazy evaluation by default.]
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnr8p1$tee$2@news.oberberg.net>
Alain Picard wrote:
> Joachim Durchholz <·················@web.de> writes:
>>Alain Picard wrote:
>>>More precisely: "macros make control of when, if, and how often,
>>>                 something is evaluated _possible_."  Functions
>>>(your only other option) give you no choice.
>>
>>This statement is wrong if left in full generality: higher-order
>>functions can control quite precisely what gets evaluated when. If the
>>language offers both lazy and strict parameters, evaluation time
>>control extends to the parameter expressions as well.
> 
> My apologies to the functional guys.  I was responding from a lisp
> newsgroup:

Ah, the joys of inadvertent crossposting ;-)

 > so let me amend the above to end with "IN LISP".

IIRC even Lisp allows you to keep expressions unevaluated via quoting. 
So macros wouldn't be the only way to control evaluation: quote the 
expression and have the callee evaluate it at a convenient time.

 > [We do not have lazy evaluation by default.]

The default evaluation strategy doesn't change too much; all you need is 
some way of deferred evaluation. It need not even be laziness, having a 
meta level (such as quoting) or access to the compiler can be used.

As I said, it's still different from macros.

Regards,
Jo
From: Roman Belenov
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <u1xsuemgp.fsf@intel.com>
Joachim Durchholz <·················@web.de> writes:

> IIRC even Lisp allows you to keep expressions unevaluated via
> quoting. So macros wouldn't be the only way to control evaluation:
> quote the expression and have the callee evaluate it at a convenient
> time.

The problem is that quoted form is just a piece of data from
compiler's point of view, so it is kept as is and has to be interpeted
in runtime (while code generated by macros is usually compiled
normally); besides, such forms can not access lexical variables in the
enclosing context (otherwise runtime environment would have to support
access to lexicals by name, which has performance implications and is
not necessary for normal compiled code). So, theoretically, you can
use quoting to control the order of evaluation, but practically it
will lead to very inefficient and less intuitive code.

-- 
 							With regards, Roman.

Standard disclaimer: I work for them, but I don't speak for them.
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnre8b$vus$1@news.oberberg.net>
Roman Belenov wrote:
> Joachim Durchholz <·················@web.de> writes:
> 
>>IIRC even Lisp allows you to keep expressions unevaluated via
>>quoting. So macros wouldn't be the only way to control evaluation:
>>quote the expression and have the callee evaluate it at a convenient
>>time.
> 
> 
> The problem is that quoted form is just a piece of data from
> compiler's point of view, so it is kept as is and has to be interpeted
> in runtime (while code generated by macros is usually compiled
> normally);

If that's the case, it's probably more due to lack of demand than due to 
serious technical issues.

 > besides, such forms can not access lexical variables in the
> enclosing context (otherwise runtime environment would have to support
> access to lexicals by name, which has performance implications and is
> not necessary for normal compiled code). So, theoretically, you can
> use quoting to control the order of evaluation, but practically it
> will lead to very inefficient  [code]

Agreed.

> and [quoting will lead to] less intuitive code.

Efficiency issues aside: how are macros more intuitive than quoting?

Regards,
Jo
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3d6cepseh.fsf@javamonkey.com>
Joachim Durchholz <·················@web.de> writes:

> Efficiency issues aside: how are macros more intuitive than quoting?

Because they let you write what you intuitively expect (assuming your
intuitions are tuned a particular way, I suppose). In Common Lisp,
WHEN is a macro that lets you write this:

  (when (> x y) (print x))

If you tried to write it as a function using quoting to prevent
evaluation you might try this:

  (when (> x y) '(print x))

which won't work in general because of the iniability for the code
inside WHEN to evaluate the data '(print x) in the lexical environment
where it appears.

Or you could do this:

  (when (> x y) #'(lambda () (print x)))

which could work but seems a bit convoluted (i.e. unintuitive)
compared to the macro version.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Joachim Durchholz
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnrlh1$3f3$1@news.oberberg.net>
Peter Seibel wrote:
> Joachim Durchholz <·················@web.de> writes:
> 
> 
>>Efficiency issues aside: how are macros more intuitive than quoting?
> 
> Or you could do this:
> 
>   (when (> x y) #'(lambda () (print x)))
> 
> which could work but seems a bit convoluted (i.e. unintuitive)
> compared to the macro version.

Um, right, but that's just a question of having the right syntactic sugar.

Regards,
Jo
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m34qxqpo50.fsf@javamonkey.com>
Joachim Durchholz <·················@web.de> writes:

> Peter Seibel wrote:
> > Joachim Durchholz <·················@web.de> writes:
> >
> >>Efficiency issues aside: how are macros more intuitive than quoting?
> > Or you could do this:
> >   (when (> x y) #'(lambda () (print x)))
> > which could work but seems a bit convoluted (i.e. unintuitive)
> > compared to the macro version.
> 
> Um, right, but that's just a question of having the right syntactic sugar.

Uh right, that's what macros are for, providing the syntactic sugar.

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Anton van Straaten
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <rHgob.11736$X22.3433@newsread2.news.atl.earthlink.net>
Peter Seibel wrote:
> Joachim Durchholz <·················@web.de> writes:
>
> > Peter Seibel wrote:
> > > Joachim Durchholz <·················@web.de> writes:
> > >
> > >>Efficiency issues aside: how are macros more intuitive than quoting?
> > > Or you could do this:
> > >   (when (> x y) #'(lambda () (print x)))
> > > which could work but seems a bit convoluted (i.e. unintuitive)
> > > compared to the macro version.
> >
> > Um, right, but that's just a question of having the right syntactic
sugar.
>
> Uh right, that's what macros are for, providing the syntactic sugar.

Yes, but the point is that with a concise syntax for lambda, entire classes
of macros can become unnecessary.  That's how Smalltalk handles 'if', for
example - no macros or special forms needed.
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3ism6nw8u.fsf@javamonkey.com>
"Anton van Straaten" <·····@appsolutions.com> writes:

> Peter Seibel wrote:
> > Joachim Durchholz <·················@web.de> writes:
> >
> > > Peter Seibel wrote:
> > > > Joachim Durchholz <·················@web.de> writes:
> > > >
> > > >>Efficiency issues aside: how are macros more intuitive than quoting?
> > > > Or you could do this:
> > > >   (when (> x y) #'(lambda () (print x)))
> > > > which could work but seems a bit convoluted (i.e. unintuitive)
> > > > compared to the macro version.
> > >
> > > Um, right, but that's just a question of having the right syntactic
> sugar.
> >
> > Uh right, that's what macros are for, providing the syntactic sugar.
> 
> Yes, but the point is that with a concise syntax for lambda, entire
> classes of macros can become unnecessary. That's how Smalltalk
> handles 'if', for example - no macros or special forms needed.

Okay, so I picked an unfortunate example in that it also falls in the
class of macros that become unecessary when other bits of syntactic
sugar are provided. How about this one.

Which is more intuitive?

This:

  (defun foo () (print "hello, world")))

Or this:

  (progn (eval-when (:compile-toplevel)
           (excl::check-lock-definitions-compile-time 'foo 'function
             'defun (fboundp 'foo))
           (push 'foo excl::.functions-defined.))
         (progn (eval-when (:compile-toplevel)
                  (excl::check-de-argdecl-change 'foo 'nil))
                (declaim (excl::dynamic-extent-arguments nil foo)))
         (setf (fdefinition 'foo)
               (let ((excl::f
                      (named-function foo
                        (lambda nil
                          (block foo (print "hello, world"))))))
                 (excl::set-func_name excl::f 'foo)
                 excl::f))
         (remprop 'foo 'excl::%fun-documentation)
         (record-source-file 'foo) 'foo)

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Marcin 'Qrczak' Kowalczyk
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <pan.2003.10.31.00.05.51.822014@knm.org.pl>
On Thu, 30 Oct 2003 23:29:00 +0000, Peter Seibel wrote:

>> Yes, but the point is that with a concise syntax for lambda, entire
>> classes of macros can become unnecessary. That's how Smalltalk
>> handles 'if', for example - no macros or special forms needed.
> 
> Okay, so I picked an unfortunate example in that it also falls in the
> class of macros that become unecessary when other bits of syntactic
> sugar are provided. How about this one.
[...]

Nobody says that *everything* should be expressed by higher order
functions. But with enough builtin syntax and concise anonymous function
notation (in particular using {} or [] for functions without arguments)
there are much fewer uses of macros than in Lisp, which has little builtin
syntax and ugly anonymous functions.

The remaining uses of macros are so rare that few languages choose to take
the cost of having macros (I mean full-blown Lisp-like macros which execute
arbitrary code at compile time and can examine its parameters).

The costs: syntax seems to be constrained to have a very regular surface
structure full of parentheses; the language must describe and implement a
representation of code as data which would otherwise be unnecessary; every
compiler must include an interpreter; it's hard to report errors to the
user showing the code as it's written in the source if the error is found
after macro expansion.

I'm not saying that the cost is obviously too high but that it's a
tradeoff, macros don't come for free. And that there are other ideas which
can replace many macros with different tradeoffs: namely a richer builtin
syntax and concise anonymous functions. In a lazy language there are yet
fewer uses of macros.

-- 
   __("<         Marcin Kowalczyk
   \__/       ······@knm.org.pl
    ^^     http://qrnik.knm.org.pl/~qrczak/
From: Peter Seibel
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3ad7inran.fsf@javamonkey.com>
Marcin 'Qrczak' Kowalczyk <······@knm.org.pl> writes:

> The remaining uses of macros are so rare ...

So, just in case it wasn't completely clear to anyone watching, this
right here is the big point of disagreement. What do you think the
"remaining uses" are and why do you say they are "rare"?[1]

Common Lispers don't consider the remaining uses we make of
macros--things like defining functions, classes, and methods, our
condition (exception) system, interfacing to C code, etc. to be all
that rare.

And that's just the stuff that's built into the language (or a
particular implementation in the case of interfacing to C). Now let's
look at a sample of the code in my personal code library: test
frameworks, regular expressions, parser generators, HTML generation,
PDF generation and typesetting, genetic programming system ... hmmm,
they all seem to use macros, some of them are practically nothing
*but* macros.

Of course in languages that don't have macros, these things are done
without macros--they are either built into the language (defining
functions) or moved out into completely external tools (parser
generators). But--as we should all recognize by now--Turing
equivalence has nothing to do with language expressiveness.

-Peter

[1] Even if the uses of macros *were* rare that's doesn't seem to be
the correct metric to balance against the "costs" of macros. Normally
we weigh costs versus benefits, right? So in a way, the higher
non-Lispers estimate the "costs" of macros (need for an code-as-data
syntax, interpreter built into the compiler, etc.), the higher they
should estimate the benefits. At least if they give Lisp programmers
*any* credit at all for making a rational choice in tool selection.
Because Common Lispers love macros and find the benefits *far*
outweigh the costs. But I guess you can explain that by assuming we're
deluded.

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Simon Taylor
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <3fa1c0d2$1@news.unimelb.edu.au>
In article <··············@javamonkey.com>, Peter Seibel wrote:
> [1] Even if the uses of macros *were* rare that's doesn't seem to be
> the correct metric to balance against the "costs" of macros. Normally
> we weigh costs versus benefits, right? So in a way, the higher
> non-Lispers estimate the "costs" of macros (need for an code-as-data
> syntax, interpreter built into the compiler, etc.), the higher they
> should estimate the benefits. At least if they give Lisp programmers
> *any* credit at all for making a rational choice in tool selection.
> Because Common Lispers love macros and find the benefits *far*
> outweigh the costs. But I guess you can explain that by assuming we're
> deluded.

No one is saying all Lispers are deluded (I hope).  There are plenty
of good ideas in Lisp, but I'd like to have them without losing the
advantages of static typing and syntax requiring minimal editor support.
Template Haskell is a good step in that direction.

Simon.
From: Pascal Costanza
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnscru$phj$1@newsreader2.netcologne.de>
Marcin 'Qrczak' Kowalczyk wrote:

> I'm not saying that the cost is obviously too high but that it's a
> tradeoff, macros don't come for free. And that there are other ideas which
> can replace many macros with different tradeoffs: namely a richer builtin
> syntax and concise anonymous functions. In a lazy language there are yet
> fewer uses of macros.

Ahh, the "in 99% of all cases" argument once again...


Pascal
From: Pascal Costanza
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnscfb$p1k$1@newsreader2.netcologne.de>
Peter Seibel wrote:

> "Anton van Straaten" <·····@appsolutions.com> writes:

>>Yes, but the point is that with a concise syntax for lambda, entire
>>classes of macros can become unnecessary. That's how Smalltalk
>>handles 'if', for example - no macros or special forms needed.
> 
> 
> Okay, so I picked an unfortunate example in that it also falls in the
> class of macros that become unecessary when other bits of syntactic
> sugar are provided.

No, I don't think so. Here is what I needed in a real program.

I had several cond statements at various places of my code. They all 
didn't have a default case. At a certain stage, I needed to be sure to 
get an exceptional return value for the default case instead of NIL. So 
I added a macro:

(defconst *error-form*
   '(mv (trans-pstate pstate :exception 'program-error) *void*))

(defmacro ev-cond* (pstate &body body)
   `(cond ,@(append body `((t (let ((pstate ,pstate)) ,*error-form*))))))

*ERROR-FORM* here is the standard code that changes a program state to a 
state with an exception and a *void* return type. EV-COND* is my 
modified COND that simply adds a default case in which PSTATE is 
correctly bound so that *ERROR-FORM* can do the right thing.

(This isn't "pure" Common Lisp, but ACL2, and the code is somewhat more 
complicated than necessary because ACL2 places some severe restrictions 
on the code that one can write.)

The essence of this is as follows:

(defmacro my-cond (&body body)
   `(cond ,@(append body '(t (handle-the-default-case))))

With simple shadowing imports one can make this completely transparent 
to client code.

How would you do this with a Smalltalk-like if expression? (This is not 
a rhetoric question - I would be really interested to hear how one could 
make this work.)


Pascal
From: Coby Beck
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnsrfd$1jbf$1@otis.netspace.net.au>
"Pascal Costanza" <········@web.de> wrote in message
·················@newsreader2.netcologne.de...
>
> The essence of this is as follows:
>
> (defmacro my-cond (&body body)
>    `(cond ,@(append body '(t (handle-the-default-case))))
>

Just to provide a more apparently general (and working ;) version, analogous
to CL's ECASE:

CL-USER 90 >
(defmacro econd (&body body)
  `(cond ,@(append body
                   `((t (error (format nil
                                       "fell through ECOND form.  could not
satisfy any of the following: ~{~%~A~}~%"
                                       (mapcar #'(lambda (cond)
                                                   (car cond))
                                               ',body))))))))
ECOND

CL-USER 91 > (econd
                ((= 3 4) "foo")
                ((= 4 4) "bar"))
"bar"

CL-USER 92 > (econd
                ((= 3 4) "foo")
                ((= 4 5) "bar"))

Error: fell through ECOND form.  could not satisfy any of the following:
(= 3 4)
(= 4 5)

  1 (abort) Return to level 0.
  2 Return to top loop level 0.

Type :b for backtrace, :c <option number> to proceed,  or :? for other
options


-- 
Coby Beck
(remove #\Space "coby 101 @ big pond . com")
From: Dirk Thierbach
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <r9f971-t51.ln1@ID-7776.user.dfncis.de>
Coby Beck <·····@mercury.bc.ca> wrote:
> 
> "Pascal Costanza" <········@web.de> wrote in message
> ·················@newsreader2.netcologne.de...
>>

>> I had several cond statements at various places of my code. They
>> all didn't have a default case. At a certain stage, I needed to be
>> sure to get an exceptional return value for the default case
>> instead of NIL. So I added a macro:

Since the overhead of evaluating it at runtime is minimal, especially
with lazyness, that's exactly the situation where it is natural to use
a HOF instead of a macro.

I didn't go through the two proposed Lisp solutions in detail, but here's
a HOF in Haskell that does the same. First a general 'cond' with an
explicit default case, then 'econd' based on cond with an error as
default case:

cond :: a -> [(Bool, a)] -> a
cond def []             = def
cond def ((True,x):_)   = x
cond def ((False,_):xs) = econd xs

econd :: [(Bool, a)] -> a
econd = cond (error "Default econd case")

> CL-USER 91 > (econd
>                ((= 3 4) "foo")
>                ((= 4 4) "bar"))
> "bar"
> 
> CL-USER 92 > (econd
>                ((= 3 4) "foo")
>                ((= 4 5) "bar"))
> 
> Error: fell through ECOND form.  

GHC Interactive, version 5.02.2, for Haskell 98.

Main> econd [(3 == 4, "foo"), (4 == 4, "bar")]
"bar"
Main> econd [(3 == 4, "foo"), (4 == 5, "bar")]
*** Exception: Default econd case


I have made the recursion of 'cond' explicit, but of course 'cond' can
be defined by a fold (and partial application):

cond' = foldr (\(guard,val) def -> if guard then val else def)


You DON'T need macros for such things. You don't need dynamic typing,
either.

- Dirk
From: Pascal Costanza
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bnummr$n7i$1@newsreader2.netcologne.de>
Dirk Thierbach wrote:

> Since the overhead of evaluating it at runtime is minimal, especially
> with lazyness, that's exactly the situation where it is natural to use
> a HOF instead of a macro.

OK, nice solution.

> I didn't go through the two proposed Lisp solutions in detail, but here's
> a HOF in Haskell that does the same. First a general 'cond' with an
> explicit default case, then 'econd' based on cond with an error as
> default case:
> 
> cond :: a -> [(Bool, a)] -> a
> cond def []             = def
> cond def ((True,x):_)   = x
> cond def ((False,_):xs) = econd xs
                             ^^^^^^^^

I guess this is a typo - it should be "cond xs", right?

> econd :: [(Bool, a)] -> a
> econd = cond (error "Default econd case")

Hmm, what if I had wanted to add a default check in front of each cond, 
instead of at the end?

Also, Coby's version prints a useful error message that mentions all 
conditions ("could not satisfy..."):

> CL-USER 91 > (econd
>                 ((= 3 4) "foo")
>                 ((= 4 4) "bar"))
> "bar"
> 
> CL-USER 92 > (econd
>                 ((= 3 4) "foo")
>                 ((= 4 5) "bar"))
> 
> Error: fell through ECOND form.  could not satisfy any of the following:
> (= 3 4)
> (= 4 5)

Would it be possible to add such a message with your proposed technique?


Pascal
From: Olaf Klischat
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <874qxpgp70.fsf@swangoose.isst.fhg.de>
"Coby Beck" <·····@mercury.bc.ca> writes:

> "Pascal Costanza" <········@web.de> wrote in message
> ·················@newsreader2.netcologne.de...
>>
>> The essence of this is as follows:
>>
>> (defmacro my-cond (&body body)
>>    `(cond ,@(append body '(t (handle-the-default-case))))
>>
>
> Just to provide a more apparently general (and working ;) version, analogous
> to CL's ECASE:
>
> CL-USER 90 >
> (defmacro econd (&body body)
>   `(cond ,@(append body
>                    `((t (error (format nil
>                                        "fell through ECOND form.  could not
> satisfy any of the following: ~{~%~A~}~%"
>                                        (mapcar #'(lambda (cond)
>                                                    (car cond))
>                                                ',body))))))))


Just for the record: Is the "append" stuff necessary? Why not write
this as

(defmacro econd (&body body)
  `(cond ,@body
	 (t (error (format nil "fell through ECOND form.  could not satisfy any of the following: ~{~%~A~}~%"
			   ',(mapcar #'(lambda (cond)
					 (car cond))
				     body))))))

?

Olaf
-- 
Olaf Klischat            | Fraunhofer ISST
Oberfeldstrasse 132      | Mollstrasse 1
12683 Berlin, Germany    | 10178 Berlin, Germany
phone: +49 30 54986231   | mail: ·············@isst.fhg.de
From: Coby Beck
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo20kb$2ggd$1@otis.netspace.net.au>
"Olaf Klischat" <·············@isst.fhg.de> wrote in message
···················@swangoose.isst.fhg.de...
> "Coby Beck" <·····@mercury.bc.ca> writes:
>
> > "Pascal Costanza" <········@web.de> wrote in message
> > ·················@newsreader2.netcologne.de...
> >>
> >> The essence of this is as follows:
> >>
> >> (defmacro my-cond (&body body)
> >>    `(cond ,@(append body '(t (handle-the-default-case))))
> >>
> >
> > Just to provide a more apparently general (and working ;) version,
analogous
> > to CL's ECASE:
> >
> > CL-USER 90 >
> > (defmacro econd (&body body)
> >   `(cond ,@(append body
> >                    `((t (error (format nil
> >                                        "fell through ECOND form.  could
not
> > satisfy any of the following: ~{~%~A~}~%"
> >                                        (mapcar #'(lambda (cond)
> >                                                    (car cond))
> >                                                ',body))))))))
>
>
> Just for the record: Is the "append" stuff necessary? Why not write
> this as
>
> (defmacro econd (&body body)
>   `(cond ,@body
> (t (error (format nil "fell through ECOND form.  could not satisfy any of
the following: ~{~%~A~}~%"
>    ',(mapcar #'(lambda (cond)
> (car cond))
>      body))))))
>

That works.  I blame Pascal for my gratuitous use of append and now I have
been exposed as one of those copy-paste-alter code monkeys without a formal
correctness proof in my head ;)

-- 
Coby Beck
(remove #\Space "coby 101 @ big pond . com")
From: Pascal Costanza
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <bo2rf6$f03$1@newsreader2.netcologne.de>
Coby Beck wrote:

> That works.  I blame Pascal for my gratuitous use of append and now I have
> been exposed as one of those copy-paste-alter code monkeys without a formal
> correctness proof in my head ;)

Why is it always my fault?!? ;)

(And, hey, my code _was_ correct!)


Pascal
From: Kenny Tilton
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <zBnob.25614$Gq.6898943@twister.nyc.rr.com>
Peter Seibel wrote:


> Which is more intuitive?
> 
> This:
> 
>   (defun foo () (print "hello, world")))

hunh???

> 
> Or this:
> 
>   (progn (eval-when (:compile-toplevel)
>            (excl::check-lock-definitions-compile-time 'foo 'function
>              'defun (fboundp 'foo))
>            (push 'foo excl::.functions-defined.))
>          (progn (eval-when (:compile-toplevel)
>                   (excl::check-de-argdecl-change 'foo 'nil))
>                 (declaim (excl::dynamic-extent-arguments nil foo)))
>          (setf (fdefinition 'foo)
>                (let ((excl::f
>                       (named-function foo
>                         (lambda nil
>                           (block foo (print "hello, world"))))))
>                  (excl::set-func_name excl::f 'foo)
>                  excl::f))
>          (remprop 'foo 'excl::%fun-documentation)
>          (record-source-file 'foo) 'foo)

oh, ok, I get it now!

kenny

-- 
http://tilton-technology.com

Why Lisp? http://alu.cliki.net/RtL%20Highlight%20Film

Your Project Here! http://alu.cliki.net/Industry%20Application
From: Roman Belenov
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <uad7hdb7p.fsf@intel.com>
Joachim Durchholz <·················@web.de> writes:

>> The problem is that quoted form is just a piece of data from
>> compiler's point of view, so it is kept as is and has to be interpeted
>> in runtime (while code generated by macros is usually compiled
>> normally);
>
> If that's the case, it's probably more due to lack of demand than due
> to serious technical issues.

IMHO it's not that simple - quoting is there to allow insertion of
literal data into program. It's not easy (and not always possible) to
deduce in compile time that some quoted expression will be used as a
code, especially if it is passed to other functions, stored in complex
data structures etc. before evaluation.

>> and [quoting will lead to] less intuitive code.
>
> Efficiency issues aside: how are macros more intuitive than quoting?

I meant quoting in Common Lisp - due to the absence of access to
lexicals data exchange between quoted and normal code is not
straightforward. If quoted and unquoted code were treated equally, it
wouldn't be a problem.

-- 
 							With regards, Roman.

Standard disclaimer: I work for them, but I don't speak for them.
From: Lex Spoon
Subject: Re: Explanation of macros; Haskell macros
Date: 
Message-ID: <m3wuapq81a.fsf@logrus.dnsalias.net>
"Robert Klemme" <········@gmx.net> writes:
> Just for the sake of my understanding: could one summarize this as "macros
> make control of *when* something is evaluated easier"?  I mean, marco
> arguments are not evaluated before the macro "call" as opposed to function
> arguments.  With that, you can decide inside the macro, how you treat
> those arguments and if you evaluate them at all.  Thx!


Yes, that's one big advantage.  If you are willing to do everything at
runtime, then HOF plus a nice general syntax for literals
(e.g. s-expressions) give you the same thing.


-Lex