From: Martin Pirstitz
Subject: Macros - Lisp novice
Date: 
Message-ID: <41178d1e$0$13326$3b214f66@tunews.univie.ac.at>
I'm currently working on the exercises in Paul Graham's ANSI Common
Lisp, specifically the ones in the chapter about macros, but there are
no solutions as reference... could someone please have a look at mine
and point out any mistakes/improvement possibilities?

;;; 10.3
;;; Define a macro that takes a number n followed by one or more
;;; expressions, and returns the value of the nth expression
;;;
;;; Probably the trivial solution, but using eval:

(defmacro nth-expr (n &rest exprs)
     `(eval (nth (1- ,n) ',exprs)))

;;; 10.3, alternate and wrong solution, doesn't work with:
;;; (let ((expr 25))
;;;   (nth-expr 2 (/ 1 0) (* expr expr)))
;;; which expands to
;;;   (apply #'* '(expr expr))

(defmacro nth-expr2 (n &rest exprs)
   (let ((expr (gensym)))
     `(let ((,expr (nth (1- ,n) ',exprs)))
        (if ,expr
          (apply (car ,expr) (cdr ,expr))
          'nil))))

;;; 10.4
;;; Define ntimes to expand into a (local) recursive function instead
;;; of a do

(defmacro ntimes (n &rest body)
   `(labels ((repeat (n)
             (when (> n 0)
               ,@body
               (repeat (1- n)))))
      (repeat ,n)))

;;; 10.5
;;; Define a macro n-of that takes a number n and an expression, and
;;; returns a list of n successive values returned by the expression

(defmacro n-of (n expr)
   (let ((i (gensym))
         (end (gensym))
         (lst (gensym)))
     `(let ((,end ,n)
            (,lst))
        (do ((,i 1 (1+ ,i)))
            ((> ,i ,end) (nreverse ,lst))
          (push ,expr ,lst)))))

;;; 10.5, alternate solution

(defmacro n-of2 (n expr)
   (let ((lst (gensym)))
     `(let ((,lst (make-list ,n)))
        (mapcar #'(lambda (,(gensym)) ,expr) ,lst))))

;;; 10.6
;;; Define a macro that takes a list of variables and a body of code,
;;; and ensures that the variables revert to their original values
;;; after the body of code is evaluated

(defmacro with-vars (vars &rest body)
   `(let ,(mapcar #'(lambda (elt) (list elt)) `,vars)
      ,@body))

;;; 10.8
;;; Define a macro that doubles its argument

(define-modify-macro double ()
   (lambda (val) (* 2 val)))


In exercies 10.3, I'm probably overlooking something obvious... i wanted
a solution without using eval, but the problem is evaluating the
arguments of the expression if they are not constant.

Which solution of exercise 10.5 is uglier? The first one (too long?),
or the second one (doesn't use the argument of the anonymous function)?

Many thanks in advance,
Martin

From: Frode Vatvedt Fjeld
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <2hoelkl5gq.fsf@vserver.cs.uit.no>
Martin Pirstitz <········@NOstudent.SPAMtuwien.ac.at> writes:

> ;;; 10.3
> ;;; Define a macro that takes a number n followed by one or more
> ;;; expressions, and returns the value of the nth expression
> ;;;
> ;;; Probably the trivial solution, but using eval:
>
> (defmacro nth-expr (n &rest exprs)
>      `(eval (nth (1- ,n) ',exprs)))

Your solution here is much better written like this:

  (defmacro nth-expr (n &rest exprs)
     `(eval ',(nth (1- n) epxrs)))

Look at the output of (macroexpand-1 '(nth-expr ...)) to see the
difference. However, this is a poorly designed macro, and most likely
not what the author had in mind.

It's not completely clear to me what nth-expr is supposed to do, but
I'd guess that the intention is not to merely evaluate expression
number n, but to transform the code such that (when the form is
evaluated) each expression is evaluated in order (for side-effects),
and then have the result(s) from expression n be returned as the value
for the nth-expr form as a whole. I.e. you want this:

  (macroexpand-1 '(nth-expr 3
                    (print i) (incf i) (isqrt i) (print i)))

To yield e.g.

  (progn
    (print i)
    (incf i)
    (multiple-value-prog1
        (isqrt i)
      (print i)))

..so that each expr is evaluated in order, but the result of the third
expr, namely (isqrt i) is the one whose result(s) are returned. Try
for yourself to write this macro.

Notice that this way, (nth-expr 1 ...) is the same as
(multiple-value-prog1 ...).

-- 
Frode Vatvedt Fjeld
From: Martin Pirstitz
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <411798df$0$16036$3b214f66@tunews.univie.ac.at>
Frode Vatvedt Fjeld wrote:

>   (defmacro nth-expr (n &rest exprs)
>      `(eval ',(nth (1- n) epxrs)))
> 
> Look at the output of (macroexpand-1 '(nth-expr ...)) to see the
> difference. However, this is a poorly designed macro, and most likely
> not what the author had in mind.

It is exactly what the author had in mind... the example given in the
book (which i probably should have included for those that don't have
it), is as follows:

 > (let ((n 2))
     (nth-expr n (/ 1 0) (+ 1 2) (/ 1 0)))
3

So the other expressions shouldn't (and in this case can't) be
evaluated.
From: Peter Seibel
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <m3oelkuwcm.fsf@javamonkey.com>
Martin Pirstitz <········@NOstudent.SPAMtuwien.ac.at> writes:

> Frode Vatvedt Fjeld wrote:
>
>>   (defmacro nth-expr (n &rest exprs)
>>      `(eval ',(nth (1- n) epxrs)))
>> Look at the output of (macroexpand-1 '(nth-expr ...)) to see the
>> difference. However, this is a poorly designed macro, and most likely
>> not what the author had in mind.
>
> It is exactly what the author had in mind... the example given in the
> book (which i probably should have included for those that don't have
> it), is as follows:
>
>  > (let ((n 2))
>      (nth-expr n (/ 1 0) (+ 1 2) (/ 1 0)))
> 3
>
> So the other expressions shouldn't (and in this case can't) be
> evaluated.

Okay, but that still doesn't mean that you need to EVAL anything. The
whole point of writing a macro is to do as much work as is possible at
compile time. How about something like this:

  (defmacro nth-expression (n &rest exprs)
    `(case ,n
      ,@(loop for i from 0 and e in exprs collect `(,i ,e))))

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Martin Pirstitz
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <4117abb9$0$18044$3b214f66@tunews.univie.ac.at>
Peter Seibel wrote:

> Okay, but that still doesn't mean that you need to EVAL anything. The
> whole point of writing a macro is to do as much work as is possible at
> compile time. How about something like this:
> 
>   (defmacro nth-expression (n &rest exprs)
>     `(case ,n
>       ,@(loop for i from 0 and e in exprs collect `(,i ,e))))
> 
> -Peter
> 

Of course, that's why I said in my original post that I wanted a
solution without using eval, but couldn't come up with one...

The 'loop' version looks nicely compact, but this macro isn't
covered until 4 chapters later in the book. I just tried to understand
its expansion, but it looks more than cryptic for beginners, to say
the least ;) What would a good solution look like without using 'loop'?

P.S.: Keep up the good work on your book! I've read the first 10
chapters so far, they're clear, concise, and easy to follow. One minor
addition I'd find helpful in the chapter about macros would be an
example where multiple backquotes are needed, and how to use them.

Martin
From: Peter Seibel
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <m3u0vctf3f.fsf@javamonkey.com>
Martin Pirstitz <········@NOstudent.SPAMtuwien.ac.at> writes:

> Peter Seibel wrote:
>
>> Okay, but that still doesn't mean that you need to EVAL anything. The
>> whole point of writing a macro is to do as much work as is possible at
>> compile time. How about something like this:
>>   (defmacro nth-expression (n &rest exprs)
>>     `(case ,n
>>       ,@(loop for i from 0 and e in exprs collect `(,i ,e))))
>> -Peter
>>
>
> Of course, that's why I said in my original post that I wanted a
> solution without using eval, but couldn't come up with one...
>
> The 'loop' version looks nicely compact, but this macro isn't
> covered until 4 chapters later in the book. I just tried to understand
> its expansion, but it looks more than cryptic for beginners, to say
> the least ;) What would a good solution look like without using 'loop'?

Well, we can translate the LOOP a few ways:

  (do ((result)
       (i 0 (incf i))
       (list exprs (rest list)))
      ((null list) (nreverse result))
    (push `(,i ,(first list)) result))

  (let ((i -1) (result ()))
    (dolist (e '(a b c) (nreverse result))
      (push `(,(incf i) ,e) result)))

  (let ((i -1)) (mapcar #'(lambda (e) `(,(incf i) ,e)) exprs))

-Peter

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

         Lisp is the red pill. -- John Fraser, comp.lang.lisp
From: Marco Baringer
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <m21xigxqk4.fsf@convey.it>
Martin Pirstitz <········@NOstudent.SPAMtuwien.ac.at> writes:

> It is exactly what the author had in mind... the example given in the
> book (which i probably should have included for those that don't have
> it), is as follows:
>
>  > (let ((n 2))
>      (nth-expr n (/ 1 0) (+ 1 2) (/ 1 0)))
> 3
>
> So the other expressions shouldn't (and in this case can't) be
> evaluated.

here's something which works respecting the current lexical
environment (which using eval doesn't):

(defmarco nth-expr (n &rest forms)
  `(case ,n
     ,@(loop for i upfrom 0
             for form in forms
             collect `(,i ,form))))

-- 
-Marco
Ring the bells that still can ring.
Forget your perfect offering.
There is a crack in everything.
That's how the light gets in.
     -Leonard Cohen
From: Frode Vatvedt Fjeld
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <2hisbsl0qh.fsf@vserver.cs.uit.no>
Martin Pirstitz <········@NOstudent.SPAMtuwien.ac.at> writes:

> It is exactly what the author had in mind... the example given in
> the book (which i probably should have included for those that don't
> have it), is as follows:
>
>  > (let ((n 2))
>      (nth-expr n (/ 1 0) (+ 1 2) (/ 1 0)))
> 3
>
> So the other expressions shouldn't (and in this case can't) be
> evaluated.

Oh.. n shouldb be evaluated, of course. That's what I failed to
realize, sorry.

As Peter Seibel writes, do try to avoid eval. Think of macros as
functions that transforms one program to another, not something that
feeds a program to an evaluator..

Anyway, nth-expr then becomes a sort of computed goto operator. CL
only offers two fundamental concepts for this: cond (or its smaller
cousin case), and function-calling. Peter Seibel provided an example
using case, here's one using function calling:

  (defmacro nth-expr (n &rest exprs)
    `(funcall (aref #(,@(mapcar (lambda (expr) `(lambda () ,expr))
                               exprs))
                    (1- ,n))))


The infamous "sufficiently smart compiler" might even compile these
two versions of nth-expr to the same code :)

-- 
Frode Vatvedt Fjeld
From: Kalle Olavi Niemitalo
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <87brhizvgf.fsf@Astalo.kon.iki.fi>
Frode Vatvedt Fjeld <······@cs.uit.no> writes:

> Peter Seibel provided an example using case, here's one using
> function calling:
>
>   (defmacro nth-expr (n &rest exprs)
>     `(funcall (aref #(,@(mapcar (lambda (expr) `(lambda () ,expr))
>                                exprs))
>                     (1- ,n))))

That doesn't work.  (nth-expr n (/ 1 0) (+ 1 2) (/ 1 0))
macroexpands to:

  (FUNCALL (AREF #((LAMBDA () (/ 1 0))
                   (LAMBDA () (+ 1 2))
                   (LAMBDA () (/ 1 0)))
                (1- N)))

The values in the vector are lambda expressions, not functions.
Here is a fixed version:

   (defmacro nth-expr (n &rest exprs)
     `(funcall (aref `#(,,@(mapcar (lambda (expr) `(lambda () ,expr))
                                   exprs))
                     (1- ,n))))

I was not convinced that I had got the nested backquotes right,
so I tried expanding the backquotes according to the rules in
section 2.4.6 of the CLHS.  Here are the steps.  Symbols
resulting from backquote expansions are in upper case; forms
beginning with them may be replaced with anything that causes
the same side effects and returns an EQUAL result.

Original form:

  `(funcall (aref `#(,,@(mapcar (lambda (expr)
                                  `(lambda () ,expr))
                                exprs))
                  (1- ,n)))

The innermost backquote is expanded first.
`(x1 x2 x3 ... xn) expansion:

  `(funcall (aref `#(,,@(mapcar (lambda (expr)
                                  `(lambda () ,expr . NIL))
                                exprs))
                  (1- ,n)))

`(x1 x2 x3 ... xn . atom) expansion:

  `(funcall (aref `#(,,@(mapcar (lambda (expr)
                                  (APPEND (LIST 'lambda) (LIST '())
                                          (LIST expr) (QUOTE NIL)))
                                exprs))
                  (1- ,n)))

Optional APPEND simplification:

  `(funcall (aref `#(,,@(mapcar (lambda (expr)
                                  (LIST 'lambda '() expr))
                                exprs))
                  (1- ,n)))

The middle backquote is expanded next.
`#(x1 x2 x3 ... xn) expansion:

  `(funcall (aref (APPLY #'VECTOR `(,,@(mapcar (lambda (expr)
                                                 (LIST 'lambda '() expr))
                                               exprs)))
                  (1- ,n)))

`(x1 x2 x3 ... xn) expansion:

  `(funcall (aref (APPLY #'VECTOR `(,,@(mapcar (lambda (expr)
                                                 (LIST 'lambda '() expr))
                                               exprs)
                                    . NIL))
                  (1- ,n)))

`(x1 x2 x3 ... xn . atom) expansion:

  `(funcall (aref (APPLY #'VECTOR
                         (APPEND (LIST ,@(mapcar (lambda (expr)
                                                   (LIST 'lambda '() expr))
                                                 exprs))
                                 (QUOTE NIL)))
                  (1- ,n)))

Optional APPEND simplification:

  `(funcall (aref (APPLY #'VECTOR
                         (LIST ,@(mapcar (lambda (expr)
                                           (LIST 'lambda '() expr))
                                         exprs)))
                  (1- ,n)))

Optional APPLY simplification (permitted by CALL-ARGUMENTS-LIMIT):

  `(funcall (aref (VECTOR ,@(mapcar (lambda (expr)
                                      (LIST 'lambda '() expr))
                                    exprs))
                  (1- ,n)))

The outermost backquote is expanded last.
`(x1 x2 x3 ... xn) expansion:

  `(funcall (aref (VECTOR ,@(mapcar (lambda (expr)
                                      (LIST 'lambda '() expr))
                                    exprs))
                  (1- ,n))
            . NIL)

`(x1 x2 x3 ... xn . atom) expansion:

  (APPEND (LIST `funcall)
          (LIST `(aref (VECTOR ,@(mapcar (lambda (expr)
                                           (LIST 'lambda '() expr))
                                         exprs))
                       (1- ,n)))
          (QUOTE NIL))

`basic and `(x1 x2 x3 ... xn) expansions:

  (APPEND (LIST 'funcall)
          (LIST `(aref (VECTOR ,@(mapcar (lambda (expr)
                                           (LIST 'lambda '() expr))
                                         exprs))
                       (1- ,n)
                       . NIL))
          (QUOTE NIL))

`(x1 x2 x3 ... xn . atom) expansion:

  (APPEND (LIST 'funcall)
          (LIST (APPEND (LIST `aref)
                        (LIST `(VECTOR ,@(mapcar (lambda (expr)
                                                   (LIST 'lambda '() expr))
                                                 exprs)))
                        (LIST `(1- ,n))
                        (QUOTE NIL)))
          (QUOTE NIL))

Optional APPEND simplification:

  (LIST 'funcall
        (APPEND (LIST `aref)
                (LIST `(VECTOR ,@(mapcar (lambda (expr)
                                           (LIST 'lambda '() expr))
                                         exprs)))
                (LIST `(1- ,n))
                (QUOTE NIL)))

`basic and `(x1 x2 x3 ... xn) expansions:

  (LIST 'funcall
        (APPEND (LIST 'aref)
                (LIST `(VECTOR ,@(mapcar (lambda (expr)
                                           (LIST 'lambda '() expr))
                                         exprs)
                               . NIL))
                (LIST `(1- ,n . NIL))
                (QUOTE NIL)))

`(x1 x2 x3 ... xn . atom) expansions:

  (LIST 'funcall
        (APPEND (LIST 'aref)
                (LIST (APPEND (LIST `VECTOR)
                              (mapcar (lambda (expr)
                                        (LIST 'lambda '() expr))
                                      exprs)
                              (QUOTE NIL)))
                (LIST (APPEND (LIST `1-)
                              (LIST n)
                              (QUOTE NIL)))
                (QUOTE NIL)))

`basic expansions:

  (LIST 'funcall
        (APPEND (LIST 'aref)
                (LIST (APPEND (LIST 'VECTOR)
                              (mapcar (lambda (expr)
                                        (LIST 'lambda '() expr))
                                      exprs)
                              (QUOTE NIL)))
                (LIST (APPEND (LIST '1-)
                              (LIST n)
                              (QUOTE NIL)))
                (QUOTE NIL)))

Optional APPEND simplification:

  (LIST 'funcall
        (LIST 'aref
              (APPEND (LIST 'VECTOR)
                      (mapcar (lambda (expr)
                                (LIST 'lambda '() expr))
                              exprs)
                      (QUOTE NIL))
              (APPEND (LIST '1-)
                      (LIST n)
                      (QUOTE NIL))))

Optional APPEND simplifications:

  (LIST 'funcall
        (LIST 'aref
              (LIST* 'VECTOR
                     (mapcar (lambda (expr)
                               (LIST 'lambda '() expr))
                             exprs))
              (LIST '1- n)))

Well, that's it.  The code is correct, even though I had doubts
about the ,,@ syntax: if ,@ expands to multiple forms, does the
comma reach to all of them?  Fortunately, the innermost backquote
is expanded first and consumes the leftmost comma before the
results of ,@ can touch it.

There seems to be a catch with the expansion of `(x1 x2 x3 ... xn
. atom).  Suppose all of the x expressions begin with ,,@ and
CALL-ARGUMENTS-LIMIT is low.  Then, the standard expansion
(append (list ,@form1) ... (list ,@formn) 'atom) won't hit the
limit as soon as the simpler alternative (list* ,@form1 ...
,@formn 'atom) does.
From: Stacy White
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <WZiSc.266544$JR4.192363@attbi_s54>
"Martin Pirstitz" <········@NOstudent.SPAMtuwien.ac.at> wrote in message
······························@tunews.univie.ac.at...
> (defmacro nth-expr (n &rest exprs)
>      `(eval (nth (1- ,n) ',exprs)))

I'm confused by the other solutions given in this thread.  Why not just use:

  (defmacro nth-expr (n &rest exprs)
       (nth (1- n) exprs))
From: Marco Baringer
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <m2acx2rq92.fsf@convey.it>
"Stacy White" <·····@computer.org> writes:

> "Martin Pirstitz" <········@NOstudent.SPAMtuwien.ac.at> wrote in message
> ······························@tunews.univie.ac.at...
>> (defmacro nth-expr (n &rest exprs)
>>      `(eval (nth (1- ,n) ',exprs)))
>
> I'm confused by the other solutions given in this thread.  Why not just use:
>
>   (defmacro nth-expr (n &rest exprs)
>        (nth (1- n) exprs))

because that would only work when n was a number, since you're passing
the _form_ n to the function nth. you'd get an error (at macro
expansion time) for a form like:

(let ((a 2))
  (nth-expr a x y z))

-- 
-Marco
Ring the bells that still can ring.
Forget your perfect offering.
There is a crack in everything.
That's how the light gets in.
     -Leonard Cohen
From: Ivan Boldyrev
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <fj6ru1xlci.ln2@ibhome.cgitftp.uiggm.nsc.ru>
On 8833 day of my life Marco Baringer wrote:
>> I'm confused by the other solutions given in this thread.  Why not just use:
>>
>>   (defmacro nth-expr (n &rest exprs)
>>        (nth (1- n) exprs))
>
> because that would only work when n was a number

But n is a number.

-- 
Ivan Boldyrev

                                       XML -- new language of ML family.
From: Marco Baringer
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <m2wu042wu3.fsf@convey.it>
Ivan Boldyrev <···············@cgitftp.uiggm.nsc.ru> writes:

> On 8833 day of my life Marco Baringer wrote:
>>> I'm confused by the other solutions given in this thread.  Why not just use:
>>>
>>>   (defmacro nth-expr (n &rest exprs)
>>>        (nth (1- n) exprs))
>>
>> because that would only work when n was a number
>
> But n is a number.

imagine:

(nth-expr (random 1) t nil)

(random 1) will, at run time, evalutate to either the number 0 or the
number 1, however the macro nth-expr will not see neither 0 nor 1,
ever, it will always see the form (RANDOM 1).

-- 
-Marco
Ring the bells that still can ring.
Forget your perfect offering.
There is a crack in everything.
That's how the light gets in.
     -Leonard Cohen
From: Ivan Boldyrev
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <i9rsu1xvlr.ln2@ibhome.cgitftp.uiggm.nsc.ru>
On 8834 day of my life Marco Baringer wrote:
>> On 8833 day of my life Marco Baringer wrote:
>>>> I'm confused by the other solutions given in this thread.  Why
>>>> not just use:
>>>>
>>>>   (defmacro nth-expr (n &rest exprs)
>>>>        (nth (1- n) exprs))
>>>
>>> because that would only work when n was a number
>>
>> But n is a number.
>
> imagine:
>
> (nth-expr (random 1) t nil)
>
> (random 1) will, at run time, evalutate to either the number 0 or the
> number 1, however the macro nth-expr will not see neither 0 nor 1,
> ever, it will always see the form (RANDOM 1).

You don't need to explain such basic things :)

I looked at wording in the book.  It is not quite clear, but example
in task passes a sexp N as first argument.

So, look at my soluition with CASE.

-- 
Ivan Boldyrev

                                       XML -- new language of ML family.
From: Christophe Rhodes
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <sqwtzw302a.fsf@cam.ac.uk>
Marco Baringer <··@bese.it> writes:

> imagine:
>
> (nth-expr (random 1) t nil)
>
> (random 1) will, at run time, evalutate to either the number 0 or the
> number 1, however the macro nth-expr will not see neither 0 nor 1,
> ever, it will always see the form (RANDOM 1).

This is the second time I've seen this error this week.  (random 1) is
constant-foldable to 0.  (This does not invalidate your point about
macro function evaluation).

Christophe
-- 
http://www-jcsu.jesus.cam.ac.uk/~csr21/       +44 1223 510 299/+44 7729 383 757
(set-pprint-dispatch 'number (lambda (s o) (declare (special b)) (format s b)))
(defvar b "~&Just another Lisp hacker~%")    (pprint #36rJesusCollegeCambridge)
From: Ivan Boldyrev
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <9daru1xdej.ln2@ibhome.cgitftp.uiggm.nsc.ru>
On 8833 day of my life Marco Baringer wrote:
> "Stacy White" <·····@computer.org> writes:
>>> (defmacro nth-expr (n &rest exprs)
>>>      `(eval (nth (1- ,n) ',exprs)))
>>
>> I'm confused by the other solutions given in this thread.  Why not just use:
>>
>>   (defmacro nth-expr (n &rest exprs)
>>        (nth (1- n) exprs))
>
> because that would only work when n was a number, since you're passing
> the _form_ n to the function nth. you'd get an error (at macro
> expansion time) for a form like:
>
> (let ((a 2))
>   (nth-expr a x y z))

I do not remember if there was such a solutin:

(defmacro nth-expr (n &rest exprs)
   (let ((cnt 0))
   `(case ,n
     ,@(mapcar #'(lambda (exp)
                   (list (incf cnt) exp))
               exprs))))

However, I insist that n is just number, not other form.

-- 
Ivan Boldyrev

                                                  Is 'morning' a gerund?
From: Ivan Boldyrev
Subject: Re: Macros - Lisp novice
Date: 
Message-ID: <9bdpu1xbhb.ln2@ibhome.cgitftp.uiggm.nsc.ru>
--=-=-=
Content-Type: text/plain

On 8831 day of my life Martin Pirstitz wrote:
> ;;; 10.3
> ;;; Define a macro that takes a number n followed by one or more
> ;;; expressions, and returns the value of the nth expression
> ;;;
> ;;; Probably the trivial solution, but using eval:
>
> (defmacro nth-expr (n &rest exprs)
>      `(eval (nth (1- ,n) ',exprs)))

(defmacro nth-expr (n &rest exprs)
    (nth (1- n) exprs))

I assume that n is always number, not variable/constant/other form...

> ;;; 10.5
> ;;; Define a macro n-of that takes a number n and an expression, and
> ;;; returns a list of n successive values returned by the expression

(defmacro n-of (n exp)
   (cons 'list
         (make-list n :initial-element exp)))

> ;;; 10.6
> ;;; Define a macro that takes a list of variables and a body of code,
> ;;; and ensures that the variables revert to their original values
> ;;; after the body of code is evaluated
>
> (defmacro with-vars (vars &rest body)
>    `(let ,(mapcar #'(lambda (elt) (list elt)) `,vars)
>       ,@body))

;;;  body must see same values, must not it?  and `,vars is vars
(defmacro with-vars (vars &rest body)
    `(let ,(mapcar #'(lambda (elt) (list elt elt)) vars)
       ,@body))

-- 
Ivan Boldyrev

              "Assembly of Japanese bicycle require great peace of mind."

--=-=-=
Content-Type: application/pgp-signature

-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.3.6 (GNU/Linux)

iD8DBQBBGgZI4rmsj66VbhcRAq6WAJ4qmpDvT05xLOgK+LIqGO0fk/8OfACfYhuN
KbcZ0WrRSLJNNjaZx7Vsvts=
=FFAF
-----END PGP SIGNATURE-----
--=-=-=--