From: Andreas Thiele
Subject: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <d7qfd0$bfs$03$1@news.t-online.com>
Hi,

is there a standard idom for extracting the documentation string when
writing macros?
I wrote the following macro defmessage which will simply ingnore it's
documentation. Is there a better, easier or more common way?

(defmacro defmessage (name (args) &body body)
  (let ((body2 (if (stringp (car body)) (cdr body) body)))
    `(progn
       (addmessage (quote ,name))
       (defmethod ,name (,args)
         ,@body2))))

(defun addmessage (name)
  (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))


Andreas

From: Pascal Bourguignon
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <87oean3uaq.fsf@thalassa.informatimago.com>
"Andreas Thiele" <······@nospam.com> writes:

> Hi,
>
> is there a standard idom for extracting the documentation string when
> writing macros?
> I wrote the following macro defmessage which will simply ingnore it's
> documentation. Is there a better, easier or more common way?
>
> (defmacro defmessage (name (args) &body body)
>   (let ((body2 (if (stringp (car body)) (cdr body) body)))
>     `(progn
>        (addmessage (quote ,name))
>        (defmethod ,name (,args)
>          ,@body2))))

(macroexpand '(defmessage get-name (stuff) "Name"))
--> (PROGN (ADDMESSAGE 'GET-NAME) (DEFMETHOD GET-NAME (STUFF)))  !!!

defmethod can handle documentation strings.  However, you might want
to collect them for example to attach them to a defgeneric instead:




> (defun addmessage (name)
>   (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))

Do you plan to delete messages from *messages*?
If not, then you could use push instead pushnew for the car of the
cons would always be different.


Perhaps you want something like:

(defmacro defmessage (name args &body body)
  (let ((docstring (when (stringp (car body)) (car body)))
        (body      (if (and (stringp (car body)) (cdr body)) (cdr body) body)))
    `(progn
       (addmessage (quote ,name))
       (defgeneric ,name ,(mapcar (lambda (x) (gensym)) args)
          ,@(when docstring `((:documentation ,docstring))))
       (defmethod  ,name ,args
         ,@body))))


[351]> (macroexpand '(defmessage get-name ((self stuff)) "Name"))
(PROGN (ADDMESSAGE 'GET-NAME)
 (DEFGENERIC GET-NAME (#:G5094) (:DOCUMENTATION "Name"))
 (DEFMETHOD GET-NAME ((SELF STUFF)) "Name")) ;
T

[352]> (macroexpand '(defmessage get-name ((self stuff)) "Name" "result"))
(PROGN (ADDMESSAGE 'GET-NAME)
 (DEFGENERIC GET-NAME (#:G5095) (:DOCUMENTATION "Name"))
 (DEFMETHOD GET-NAME ((SELF STUFF)) "result")) ;
T

[353]> (macroexpand '(defmessage get-name ((self stuff)) :result))
(PROGN (ADDMESSAGE 'GET-NAME) (DEFGENERIC GET-NAME (#:G5096))
 (DEFMETHOD GET-NAME ((SELF STUFF)) :RESULT)) ;
T

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

In a World without Walls and Fences, 
who needs Windows and Gates?
From: Andreas Thiele
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <d7rtan$e0g$05$1@news.t-online.com>
"Pascal Bourguignon" <···@informatimago.com> schrieb im Newsbeitrag
···················@thalassa.informatimago.com...
> "Andreas Thiele" <······@nospam.com> writes:
>
> > Hi,
> >
> > is there a standard idom for extracting the documentation string when
> > writing macros?
> > I wrote the following macro defmessage which will simply ingnore it's
> > documentation. Is there a better, easier or more common way?
> >
> > (defmacro defmessage (name (args) &body body)
> >   (let ((body2 (if (stringp (car body)) (cdr body) body)))
> >     `(progn
> >        (addmessage (quote ,name))
> >        (defmethod ,name (,args)
> >          ,@body2))))
>
> (macroexpand '(defmessage get-name (stuff) "Name"))
> --> (PROGN (ADDMESSAGE 'GET-NAME) (DEFMETHOD GET-NAME (STUFF)))  !!!
>
> defmethod can handle documentation strings.  However, you might want
> to collect them for example to attach them to a defgeneric instead:

Yes, I already noticed this.

Perhaps sometimes people doing nothing at all are better off - they don't
make mistakes :-))

Now I think ignoring the documentation is the best way, because it will get
assigned to the method.

> > (defun addmessage (name)
> >   (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))
>
> Do you plan to delete messages from *messages*?
> If not, then you could use push instead pushnew for the car of the
> cons would always be different.

No, I don't delete messages, but I still think I shouldn't use push. The
methods name should appear only once in the association list - the name is
unique thus I used :key 'cdr. The same message might get redefined during
development. I this case it gets a new id, but it's name would appear only
once in the list.

> Perhaps you want something like:
>
> (defmacro defmessage (name args &body body)
>   (let ((docstring (when (stringp (car body)) (car body)))
>         (body      (if (and (stringp (car body)) (cdr body)) (cdr body)
body)))
>     `(progn
>        (addmessage (quote ,name))
>        (defgeneric ,name ,(mapcar (lambda (x) (gensym)) args)
>           ,@(when docstring `((:documentation ,docstring))))
>        (defmethod  ,name ,args
>          ,@body))))
> ...

Great, I like this version. Although I must admit, these methods are not
really generic. I misuse defmethod here to have a 'type check' and a little
improved readability. My messages are just a few (abt 20) functions who's
name are automatically translated into numbers and sent to the internet.
Later I receive numbers from the internet together with parameters which get
translated back in the proper function call.

My original question was about extracting the documentation information.
Obviously you use the same procedure - you extract the car of the body.
Thus, I think, you don't use another idiom.

Thanks for your help

Andreas


P.S. For completeness - I ended up with the following code, like before :-))
:

(defvar *messages* nil)

(defgeneric message (message)
  (:documentation "Translation between message symbol and message id"))

(defmethod message ((name symbol))
  (car (rassoc name *messages*)))

(defmethod message ((id number))
  (cdr (assoc id *messages*)))

(defun addmessage (name)
  (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))

(defmacro defmessage (name args &body body)
  `(progn
     (addmessage (quote ,name))
     (defmethod ,name ,args
       ,@body)))
From: Pascal Bourguignon
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <87k6la87j5.fsf@thalassa.informatimago.com>
"Andreas Thiele" <······@nospam.com> writes:
>> > (defun addmessage (name)
>> >   (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))
>>
>> Do you plan to delete messages from *messages*?
>> If not, then you could use push instead pushnew for the car of the
>> cons would always be different.
>
> No, I don't delete messages, but I still think I shouldn't use push. The
> methods name should appear only once in the association list - the name is
> unique thus I used :key 'cdr. 

Oh, right.  I never noticed you can use :key with pushnew.  Thanks.

> The same message might get redefined during
> development. I this case it gets a new id, but it's name would appear only
> once in the list.

    (defparameter l '((:a . 1) (:b . 2)))
--> L

    (pushnew '(:c . 3) l :key (function car))
--> ((:C . 3) (:A . 1) (:B . 2))

    (pushnew '(:a . 4) l :key (function car))
--> ((:C . 3) (:A . 1) (:B . 2))
              ^^^^^^^^

The old cons is not replaced.

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

In a World without Walls and Fences, 
who needs Windows and Gates?
From: Andreas Thiele
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <d7smql$rhg$00$1@news.t-online.com>
"Pascal Bourguignon" <···@informatimago.com> schrieb im Newsbeitrag
···················@thalassa.informatimago.com...
> "Andreas Thiele" <······@nospam.com> writes:
> >> > (defun addmessage (name)
> >> >   (pushnew (cons (1+ (length *messages*)) name) *messages* :key
'cdr))
> >>
> >> Do you plan to delete messages from *messages*?
> >> If not, then you could use push instead pushnew for the car of the
> >> cons would always be different.
> >
> > No, I don't delete messages, but I still think I shouldn't use push. The
> > methods name should appear only once in the association list - the name
is
> > unique thus I used :key 'cdr.
>
> Oh, right.  I never noticed you can use :key with pushnew.  Thanks.
>
> > The same message might get redefined during
> > development. I this case it gets a new id, but it's name would appear
only
> > once in the list.
>
>     (defparameter l '((:a . 1) (:b . 2)))
> --> L
>
>     (pushnew '(:c . 3) l :key (function car))
> --> ((:C . 3) (:A . 1) (:B . 2))
>
>     (pushnew '(:a . 4) l :key (function car))
> --> ((:C . 3) (:A . 1) (:B . 2))
>               ^^^^^^^^
>
> The old cons is not replaced.
> ...

Ooops! Yes ...

This indeed just scared me, but - fortunately - in my situation it is
absolutely OK. I mean thats what pushnew is for. My above explanation was
wrong. This is an very old part of my application and obviously quick
reading of my own source resulted in a wrong explanation.

In my program this means, once a message is assigned to an ID, this ID will
never change and IDs will stay unique. If my addmessage tries to add an
already registered message (by re-evaluating a modified defmessage
definition), pushnew will silently fail. (I didn't recall this correctly
:)) ).

(Rem: If I delete a message this means I purge a function from my source. At
this moment the name is still registered. That does no harm because
invocation will take place by resolving the name to an ID and next time I
load the whole application, this list would be OK again. Indeed I never
deleted one of those methods, just added new ones.)

Thanks for the hint

Andreas
From: Andreas Thiele
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <d7s1ii$ff9$00$1@news.t-online.com>
"Pascal Bourguignon" <···@informatimago.com> schrieb im Newsbeitrag
···················@thalassa.informatimago.com...
> "Andreas Thiele" <······@nospam.com> writes:
> ..

> ..
> Perhaps you want something like:
>
> (defmacro defmessage (name args &body body)
>   (let ((docstring (when (stringp (car body)) (car body)))
>         (body      (if (and (stringp (car body)) (cdr body)) (cdr body)
body)))
> ...

Ooops,

after re-reading your post I noticed the meaning of additionally testing
(cdr body). If (cdr body) is nil, docstring is the only form in body and
probably should stay there as return value.

> ...
>     `(progn
>        (addmessage (quote ,name))
>        (defgeneric ,name ,(mapcar (lambda (x) (gensym)) args)
>           ,@(when docstring `((:documentation ,docstring))))
>        (defmethod  ,name ,args
>          ,@body))))
> ...
From: Wade Humeniuk
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <W48oe.42498$tt5.34121@edtnps90>
Andreas Thiele wrote:
> Hi,
> 
> is there a standard idom for extracting the documentation string when
> writing macros?
> I wrote the following macro defmessage which will simply ingnore it's
> documentation. Is there a better, easier or more common way?
> 
> (defmacro defmessage (name (args) &body body)
>   (let ((body2 (if (stringp (car body)) (cdr body) body)))
>     `(progn
>        (addmessage (quote ,name))
>        (defmethod ,name (,args)
>          ,@body2))))
> 
> (defun addmessage (name)
>   (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))
> 

Here is another way,

(defmacro defmessage (name (args) &body body)
   `(progn
      (addmessage (quote ,name))
      (let ((method (defmethod ,name (,args) ,@body)))
        (setf (documentation method t) nil)
        method)))

(defvar *messages* nil)
(defun addmessage (name)
   (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))

CL-USER 10 > (defmessage add9 ((i integer))
                "Add 9 to I"
                (+ i 9))
#<STANDARD-METHOD ADD9 NIL (INTEGER) 20687784>

CL-USER 11 > (documentation * t)
NIL

as opposed to

CL-USER 15 > (defmethod add8 ((i integer))
                "Add 8 to I"
                (+ i 9))
#<STANDARD-METHOD ADD8 NIL (INTEGER) 2069698C>

CL-USER 16 > (documentation * t)
"Add 8 to I"
From: Andreas Thiele
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <d7s11h$ees$00$1@news.t-online.com>
"Wade Humeniuk" <··················@telus.net> schrieb im Newsbeitrag
··························@edtnps90...
> Andreas Thiele wrote:
> > Hi,
> >
> > is there a standard idom for extracting the documentation string when
> > writing macros?
> > I wrote the following macro defmessage which will simply ingnore it's
> > documentation. Is there a better, easier or more common way?
> >
> > (defmacro defmessage (name (args) &body body)
> >   (let ((body2 (if (stringp (car body)) (cdr body) body)))
> >     `(progn
> >        (addmessage (quote ,name))
> >        (defmethod ,name (,args)
> >          ,@body2))))
> >
> > (defun addmessage (name)
> >   (pushnew (cons (1+ (length *messages*)) name) *messages* :key 'cdr))
> >
>
> Here is another way,
>
> (defmacro defmessage (name (args) &body body)
>    `(progn
>       (addmessage (quote ,name))
>       (let ((method (defmethod ,name (,args) ,@body)))
>         (setf (documentation method t) nil)
>         method)))
>  ...

OK, OK - of course you are right - funny solution :))

It's my fault because I posted the code under consideration, thus misleading
the reader to other questions which can arise.

Perhaps I should have posted a more symbolic example like:

(defmacro macro-with-special-docu-handling (name args &body body)
  (let ((docu (when (stringp (car body)) (car body)))
        (body (if (stringp (car body)) (cdr body) body)))
    `(progn
       ,@(an-arbitrary-transformation-of name args docu body))))

Now my question is, if there is a better way of extracting the documetation
than applying car to body?
I think there is no way to do it by destructuring?

Thanks


Andreas
From: Marco Baringer
Subject: Re: Lisp idiomatic: macros and documentation?
Date: 
Message-ID: <m2zmu6l7al.fsf@soma.local>
"Andreas Thiele" <······@nospam.com> writes:

> Now my question is, if there is a better way of extracting the documetation
> than applying car to body?
> I think there is no way to do it by destructuring?

(defun split-body-into-parts (body)
  "Returns the declares, the doc string, and any forms in BODY."
  (flet ((ret (dec doc body)
           (return-from split-body-into-parts (values dec
                                                      (when doc
                                                        (list doc))
                                                      body))))
    (loop
       with doc-string = nil
       with declares = '()
       for form* on body
       for form = (car form*)
       do (cond
            ((and (stringp form) (cdr form*))
             (setf doc-string form))
            ((stringp form)
             (ret declares doc-string form*))
            ((and (consp form) (eql 'cl:declare (car form)))
             (push form declares))
            (t
             (ret declares doc-string form*))))))

you may not need to worry about this but, normally, where you find doc
strings you can also find declare forms and they can be mixed up
arbitrarily (the only limit, afaict, is that the first literal string
encountered is the doc string).

-- 
-Marco
Ring the bells that still can ring.
Forget the perfect offering.
There is a crack in everything.
That's how the light gets in.
	-Leonard Cohen