From: Joerg Hoehle
Subject: destructuring-bind on infinite lists?
Date: 
Message-ID: <uoe0ym1an.fsf@users.sourceforge.net>
Hi,

Nathan Froyd submitted a bug-report to clisp about the following:
(defvar *vars* '#1=(a b c d e . #1#))

(destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
;add (declare (ignore ignore)) is you wish
-> error in clisp-2.38 and cmucl-19c

I went through CLHS, found the dotted list paragraphs and yet it's not
clear to me whether CLHS requires the above to work.

It appears that both cmucl19c and clisp error out by using
(dotted-)list-length to detect the case of dotted lists.  Of course,
cdr-infinite lists are not dotted.
Are such "lists" acceptable to destructuring-bind?

I wonder whether there are other implications, like "infinite only
acceptable where dotted lists are acceptable as well"?

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center

From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1140732541.788461.178190@i39g2000cwa.googlegroups.com>
Joerg Hoehle wrote:
> Hi,
>
> Nathan Froyd submitted a bug-report to clisp about the following:
> (defvar *vars* '#1=(a b c d e . #1#))
>
> (destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
> ;add (declare (ignore ignore)) is you wish
> -> error in clisp-2.38 and cmucl-19c

> It appears that both cmucl19c and clisp error out by using
> (dotted-)list-length to detect the case of dotted lists.

I think that destructuring bind should not be calculating the list
length, for efficiency reasons, never mind calculating the length with
a function that can detect cycles!

You shouldn't have to pay such penalties just because you want
syntactic sugar for extracting a few things.
From: Joerg Hoehle
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <ubqwxm77j.fsf@users.sourceforge.net>
"Kaz Kylheku" <········@gmail.com> writes:
> > (destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
> I think that destructuring bind should not be calculating the list
> length, for efficiency reasons, never mind calculating the length with
> a function that can detect cycles!

I concur that ideally, d-b should expand to
(if (consp arg)
  (let ((a (car arg)) (arg (cdr arg)))
    (if (consp arg)
      (let ((b (car arg)) (arg (cdr arg)))
        ...
        ,@body)
      (error 'program-error)))
  (error 'program-error))

However I can understand that given the huge number of possibilities
that d-b offers, implementations choose another implementation
strategy that produces different code.  A typical such strategy is

"check first for errors, then work on checked data structures"
This sounds like a very reasonable and widely known strategy.
It may produce
(if ,(some-tests) (error 'program-error)
  (let ((a (car arg)) (b (cadr arg)) ...)
    ,@body))

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Raymond Toy
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <sxdk6bl4po7.fsf@rtp.ericsson.se>
>>>>> "Joerg" == Joerg Hoehle <······@users.sourceforge.net> writes:

    Joerg> Hi,
    Joerg> Nathan Froyd submitted a bug-report to clisp about the following:
    Joerg> (defvar *vars* '#1=(a b c d e . #1#))

    Joerg> (destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
    Joerg> ;add (declare (ignore ignore)) is you wish
    -> error in clisp-2.38 and cmucl-19c

Not quite relevant, but this has been fixed in the snapshots post
19c.

Ray
From: Pascal Costanza
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <466um5F9p0g8U1@individual.net>
Joerg Hoehle wrote:
> Hi,
> 
> Nathan Froyd submitted a bug-report to clisp about the following:
> (defvar *vars* '#1=(a b c d e . #1#))
> 
> (destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
> ;add (declare (ignore ignore)) is you wish
> -> error in clisp-2.38 and cmucl-19c
> 
> I went through CLHS, found the dotted list paragraphs and yet it's not
> clear to me whether CLHS requires the above to work.

Yes, CLHS requires the above to work.

3.4.5 Destructuring Lambda Lists: "A destructuring lambda list can 
contain all of the lambda list keywords listed for macro lambda lists 
except for &environment, and supports destructuring in the same way."

3.4.4 Macro Lambda Lists: "It is permissible for a macro form (or a 
subexpression of a macro form) to be a dotted list only when (... &rest 
var) or (... . var) is used to match it."

"14.1.2.3 General Restrictions on Parameters that must be Lists" which 
states that "any standardized function that takes a parameter that is 
required to be a list should be prepared to signal an error of type 
type-error if the value received is a dotted list" does not apply 
because destructuring-bind is a macro, not a function.


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Barry Margolin
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <barmar-9FCED8.23090623022006@comcast.dca.giganews.com>
In article <··············@individual.net>,
 Pascal Costanza <··@p-cos.net> wrote:

> Joerg Hoehle wrote:
> > Hi,
> > 
> > Nathan Froyd submitted a bug-report to clisp about the following:
> > (defvar *vars* '#1=(a b c d e . #1#))
> > 
> > (destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
> > ;add (declare (ignore ignore)) is you wish
> > -> error in clisp-2.38 and cmucl-19c
> > 
> > I went through CLHS, found the dotted list paragraphs and yet it's not
> > clear to me whether CLHS requires the above to work.
> 
> Yes, CLHS requires the above to work.
> 
> 3.4.5 Destructuring Lambda Lists: "A destructuring lambda list can 
> contain all of the lambda list keywords listed for macro lambda lists 
> except for &environment, and supports destructuring in the same way."
> 
> 3.4.4 Macro Lambda Lists: "It is permissible for a macro form (or a 
> subexpression of a macro form) to be a dotted list only when (... &rest 
> var) or (... . var) is used to match it."
> 
> "14.1.2.3 General Restrictions on Parameters that must be Lists" which 
> states that "any standardized function that takes a parameter that is 
> required to be a list should be prepared to signal an error of type 
> type-error if the value received is a dotted list" does not apply 
> because destructuring-bind is a macro, not a function.

You seem to be quoting requirements related to dotted lists.  Since his 
issue is with circular lists, not dotted lists, what's the relevance?

-- 
Barry Margolin, ······@alum.mit.edu
Arlington, MA
*** PLEASE post questions in newsgroups, not directly to me ***
*** PLEASE don't copy me on replies, I'll read them in the group ***
From: Pascal Costanza
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <467vg7F9uirhU1@individual.net>
Barry Margolin wrote:

> You seem to be quoting requirements related to dotted lists.  Since his 
> issue is with circular lists, not dotted lists, what's the relevance?

Indeed, it's not relevant. Sorry...


Pascal

-- 
My website: http://p-cos.net
Closer to MOP & ContextL:
http://common-lisp.net/project/closer/
From: Joerg Hoehle
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <ufym9m7la.fsf@users.sourceforge.net>
I wrote:
> (defvar *vars* '#1=(a b c d e . #1#))
> (destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
> It appears that both cmucl19c and clisp error out

Just in case somebody is eager to respond that this must be allowed, I
considered the following, more evolved case:
(defparameter *vars* '#1=(:test a :foo b . #1#))
(destructuring-bind (a b c d &rest ignore &key test &allow-other-keys) *vars* (list a b c d test))

While sbcl 0.9.2 passes the first test, it dumps core in GC on the
latter one, with a message about LDB not being present (Ubuntu/Debian sbcl).

It seems to me like the only case where an implementation may choose
to allow infinite lists is when &rest is equivalent to the
old-fashioned dot notation that d-b also supports, e.g.
(d-b (a b c d e . ignore) ...)
Note that you cannot write
(d-b (a b c d e . ignore &key ...) ...)

In another thread somebody noticed that one can replace the &rest
variable with another destructuring pattern, e.g. &rest (x y)
(d-b (a b &rest (x y)) ...)
should(?) be equivalent to
(d-b (a b x y) ...)
-- as using the dotted notation easily reveals.

However, in clisp CVS:
(destructuring-bind (a b &rest (c d)) '(1 2 3 4 . 5) (list a b c d))
 -> (1 2 3 4)
which seems an error.

This pattern shows that &rest without &key is not enough indication
that infinite lists could be accepted: in this example d-b should
accept only a proper list of 4 elements.

Given that number of restrictions, do you really believe that infinite
lists make sense with destruturing-bind?

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1140796997.791783.292070@z34g2000cwc.googlegroups.com>
Joerg Hoehle wrote:
> I wrote:
> > (defvar *vars* '#1=(a b c d e . #1#))
> > (destructuring-bind (a b c d e &rest ignore) *vars* (list a b c d e))
> > It appears that both cmucl19c and clisp error out
>
> Just in case somebody is eager to respond that this must be allowed, I
> considered the following, more evolved case:
> (defparameter *vars* '#1=(:test a :foo b . #1#))
> (destructuring-bind (a b c d &rest ignore &key test &allow-other-keys) *vars* (list a b c d test))
>
> While sbcl 0.9.2 passes the first test, it dumps core in GC on the
> latter one, with a message about LDB not being present (Ubuntu/Debian sbcl).
>
> It seems to me like the only case where an implementation may choose
> to allow infinite lists is when &rest is equivalent to the
> old-fashioned dot notation that d-b also supports, e.g.
> (d-b (a b c d e . ignore) ...)
> Note that you cannot write
> (d-b (a b c d e . ignore &key ...) ...)

I did a lot of digging around in the HyperSpec about this matter last
night and basically came to these  observations conclusions:

1. Destructuring is done to atoms and conses that behave like a tree
   structure, not a list. So one has to look for requirements and
   constraints with regard to tree structures being used as input to
   the macro.
2. Circular tree structures are banned from standard functions unless
   otherwise noted, but of course, DESTRUCTURING-BIND isn't a function.
3. The description of destructuring semantics is split into two cases:
   - the destructuring lambda list has no lambda list keywords -
   the destructuring lambda list has keywords In the no-keyword case,
   the requirement is that the input be a compatible tree structure,
   which, when you interpret the text, means this: the input is either
   equivalent to the structure or greater. Equivalent means that
   the input has a cons cell wherever the pattern has a cons cell:
   you can navigate it in the same way. When you hit a leaf (atom)
   in the pattern, there is also atom, quite possibly a different one,
   in the input. That the input can be greater means that an atom in
   the pattern can also match a cons.
4. In my opinion, the tree matching must stop when an atom in the
   lambda list is found, whether it matches an atom in the input or
   a cons. There is no need whatsoever to crack open the "leaf cons"
   in the input object which matches a leaf atom in the pattern, so
   an implementation which does that is doing something quite bad:
   it's looking at data which is irrelevant to the computation that it
   has to perform, and therefore wasting time. If, in addition, it can
   /break/ because of the features of that data, it is an unacceptably
   bad implementation.  It's like the recently discussed bug in Corman
   Lisp whereby a division by zero in a constant expression that
   is not evaluated breaks the compiler: the compiler is evaluating
   something that it should not be.  The input tree structure ought
   to be navigated only to the depths and breadths indicated by the
   destructuring pattern, as if this were done by functions in the
   Cons Dictionary.
5. If there are lambda keywords, the requirement is that the
   matching is done in the same way as in the no-keyword case, right
   up to the first keyword. Each item to the left of the first keyword
   is recursively taken to be a destructuring pattern, and is applied
   to the corresponding element of the input. What happens with the
   keywords must be examined individually according to the semantics
   of each keyword.
6. &rest should have no problems with circularity, since it is followed
   by exactly one destructuring pattern which matches the rest of the
   list.  In fact, the &rest keyword calls for a shallower navigation
   of the input structure than a pattern not preceded by &rest. The
   lambda list (&rest x) just matches the whole input object, atom
   or cons, whereas (x) requires the input to be a cons, and matches
   the car.  A reasonable macro expansion of
   (destructuring-bind (&rest x) y z) is (let ((x y)) z).
   (&rest (x y ...)) is equivalent to (x y ...).
7. On the other hand &key has problems with circularity because it
   contains an implicit property list search, which can fail to
   terminate on an circular property list.
8. Because some keywords can have problems with circularity, it's not
   possible to state a general requirement that destructuring
   must work with circular tree structures on input.  Because then
   implementations of &key would have to perform cycle detection,
   rendering them inefficient.


> In another thread somebody noticed that one can replace the &rest
> variable with another destructuring pattern, e.g. &rest (x y)

Correct. Anywhere a variable may appear in a function lambda list, a
destructuring lambda list can have a destructuring pattern. (Except
that if there is any ambiguity between a list syntax that is normally
allowed in a lambda list and a destructuring pattern, the
interpretation is in favor of list syntax).

> However, in clisp CVS:
> (destructuring-bind (a b &rest (c d)) '(1 2 3 4 . 5) (list a b c d))
>  -> (1 2 3 4)
> which seems an error.

No. (a b &rest (c d)) is equivalent to the non-keyword lambda list (a b
c d).
Matched against (1 2 3 4 . 5), the A ... D take 1 ... 4, and the 5 is
ignored.

The 5 could be extracted like this:

  (a b & rest (c d . e))

or

  (a b &rest (c d & rest e))

You have to split it into the two cases: match everything up to the
first lambda list keyword, so in other words as if (a b) were being
matched against the input. The A and B take the 1 and 2.
Then &REST means that the rest of the list, namely (3 4 . 5) is matched
against (c d).

> This pattern shows that &rest without &key is not enough indication
> that infinite lists could be accepted: in this example d-b should
> accept only a proper list of 4 elements.

Ah, but destructuring takes its input to be a tree structure, not a
list. So the proper-improper terminology doesn't even apply.

> Given that number of restrictions, do you really believe that infinite
> lists make sense with destruturing-bind?

I absolutely believe that infinite tree structures make sense with
destructuring bind, and that the implementations of destructuring-bind
that we are seeing discussed in this thread are broken piles of crap
that generate horrible code.

Destructuring should not only allow the programmer to be more
expressive, but it should also be way more efficient than naive
hand-written destructuring, wherever possible.

For instance the simple pattern (a b c d e ...) elements should not
retrieve each element by scanning the list from the beginning, but
rather use an iterator that marches through the list and picks up each
element in turn. Scanning from the beginning means that the time spent
is N squared in the size of the pattern, when in fact it could be
linear. That can matter, and the break-even point probably occurs at a
very small number of items.

Using any kind of length function for handling any aspect of the tree
structure matching is absolutely unacceptable, let alone a length
function that has cycle detection!

Why use a length function that can terminate in the face of cycles, if
the overall construct is going to break on cyclic inputs? That is so
inconsistent, it can only be a bug.

It seems that we need a decent destructuring engine that puts out nice
code and does not look at parts of the input that it doesn't have to.
From: Joerg Hoehle
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <uslq2ht38.fsf@users.sourceforge.net>
I wrote:
> (defparameter *vars* '#1=(:test a :foo b . #1#))
> (destructuring-bind (a b c d &rest ignore &key test &allow-other-keys) *vars* (list a b c d test))
> While sbcl 0.9.2 passes the first test, it dumps core in GC on the
> latter one, with a message about LDB not being present (Ubuntu/Debian sbcl).

Could somebody please test this with a later sbcl?  I would not want
to submit a bug-report to the sbcl people if this is old news & fixed.

Thanks,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Christophe Rhodes
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <sqek1m7xqg.fsf@cam.ac.uk>
Joerg Hoehle <······@users.sourceforge.net> writes:

> I wrote:
>> (defparameter *vars* '#1=(:test a :foo b . #1#))
>> (destructuring-bind (a b c d &rest ignore &key test &allow-other-keys) *vars* (list a b c d test))
>> While sbcl 0.9.2 passes the first test, it dumps core in GC on the
>> latter one, with a message about LDB not being present (Ubuntu/Debian sbcl).
>
> Could somebody please test this with a later sbcl?  I would not want
> to submit a bug-report to the sbcl people if this is old news & fixed.

It's still broken in 0.9.10.  Please submit a bug.

Christophe
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1140935656.409275.243410@t39g2000cwt.googlegroups.com>
This thread has prompted me to think about a better DESTRUCTURING-BIND
implementation. As in, one that does not do silly things, like perform
length computations that are robust against cycles (but then fail
anyway). Or other silly things, like walking from the root of the tree
structure to fetch the value for each darn binding!

So here is a little germ of an implementation that I have started. It
does not handle lambda keywords, only data-like matching.

The basic design is simple. Take the input pattern, and reduce it to a
flat sequence of instructions in the form (<temporary-variable>
<expression>). The temporaries are generated using gensym as needed.
The first instruction is (<temporary-variable> <input-expression>)
where the input expression is the one that comes in from the binding
macro that evaluates to a tree structure. And sometimes instead of a
temporary variable, you substitute a symbol found in the pattern: an
actual variable from the binding construct.

These instructions are then simply rolled up into a LET* construct
together with body forms, and it's done.

Optimization can be done by making passes over the instructions, taking
care never to eliminate a non-temporary variable. But perhaps the Lisp
compiler itself can do a good job here, so eliminating the temporaries
before the compiler won't buy anything other than a slicker
macroexpansion.

Anyway, here is that little germ:

(defpackage #:dstr
  (:use cl)
  (:export expander bind))

(in-package #:dstr)

(defun checked-car (cons)
  (if (atom cons)
    (error "incompatible tree structure: cons in pattern matched by ~s"
cons)
    (car cons)))

(defun checked-cdr (cons)
  (if (atom cons)
    (error "incompatible tree structure: cons in pattern matched by ~s"
cons)
    (cdr cons)))

(defun expander (pattern in-temp-var)
  (cond
    ((null pattern) nil)
    ((symbolp pattern)
     `((,pattern ,in-temp-var)))
    ((consp pattern)
     (let ((car-temp (gensym))
           (cdr-temp (gensym)))
       `((,car-temp (checked-car ,in-temp-var))
         ,@(expander (car pattern) car-temp)
         (,cdr-temp (checked-cdr ,in-temp-var))
         ,@(expander (cdr pattern) cdr-temp))))
    (t (error "non-symbol leaf ~a in destructuring pattern") pattern)))

(defmacro bind (pattern tree-form &body body-forms)
  (let ((eval-to (gensym)))
    `(let* ((,eval-to ,tree-form)
            ,@(expander pattern eval-to))
       ,@body-forms)))

Example runs:

(macroexpand '(dstr:bind (a ((b c) d) e f) x y z))

--->

(LET*
 ((#:G2817 X) (#:G2818 (DSTR::CHECKED-CAR #:G2817)) (A #:G2818)
  (#:G2819 (DSTR::CHECKED-CDR #:G2817)) (#:G2820 (DSTR::CHECKED-CAR
#:G2819))
  (#:G2822 (DSTR::CHECKED-CAR #:G2820)) (#:G2824 (DSTR::CHECKED-CAR
#:G2822))
  (B #:G2824) (#:G2825 (DSTR::CHECKED-CDR #:G2822))
  (#:G2826 (DSTR::CHECKED-CAR #:G2825)) (C #:G2826)
  (#:G2827 (DSTR::CHECKED-CDR #:G2825)) (#:G2823 (DSTR::CHECKED-CDR
#:G2820))
  (#:G2828 (DSTR::CHECKED-CAR #:G2823)) (D #:G2828)
  (#:G2829 (DSTR::CHECKED-CDR #:G2823)) (#:G2821 (DSTR::CHECKED-CDR
#:G2819))
  (#:G2830 (DSTR::CHECKED-CAR #:G2821)) (E #:G2830)
  (#:G2831 (DSTR::CHECKED-CDR #:G2821)) (#:G2832 (DSTR::CHECKED-CAR
#:G2831))
  (F #:G2832) (#:G2833 (DSTR::CHECKED-CDR #:G2831)))
 Y Z)


(dstr:bind (a ((b c) d) e f) (list 1 2) (list a b c d e f ))

--> error: incompatible tree structure: cons in pattern matched by 2


(dstr:bind (a ((b c) d) e f) '(1 ((2 3) 4) 5 6) (list a b c d e f))

--> (1 2 3 4 5 6)


How about some timing just for fun? Let's start with CLISP 2.38, Fedora
Core 4, old 400 Mhz Celeron. I added some (DECLAIM (INLINE's )) for the
CHECKED-CAR and CHECKED-CDR functions.

(defun test-1 ()
  (dstr:bind (a ((b c) d) e f) '(1 ((2 3) 4) 5 6) (list a b c d e f)))

(defun test-2 ()
  (destructuring-bind (a ((b c) d) e f) '(1 ((2 3) 4) 5 6) (list a b c
d e f)))

(defun test ()
  (time (dotimes (x 100000) (test-1)))
  (time (dotimes (x 100000) (test-2))))

(test)

Real time: 9.345681 sec.
Run time: 9.34058 sec.
Space: 4800000 Bytes
GC: 9, GC time: 0.308954 sec.
Real time: 4.204566 sec.
Run time: 4.205361 sec.
Space: 4800000 Bytes
GC: 10, GC time: 0.337946 sec.

Okay, we lose big time in interpreted mode: more than twice as slow.
It's not quite fair because DESTRUCTURING-BIND, even in code that is
not compiled, produces an expansion that calls into compiled functions,
whereas our CHECKED-CAR/CDR are interpreted.

(compile 'test-1)
(compile 'test-2)
(compile 'test)

(test)
Real time: 0.665029 sec.
Run time: 0.664899 sec.
Space: 4800000 Bytes
GC: 9, GC time: 0.304952 sec.
Real time: 0.896041 sec.
Run time: 0.888865 sec.
Space: 4800000 Bytes
GC: 9, GC time: 0.334949 sec.

Better! Now the DSTR:BIND test is 33% faster.

CLISP's latest DESTRUCTURING-BIND has a similar approach: a LET* ladder
with gensyms that walks through the input tree once. But it uses
regular CAR and CDR. The structure compatibility checks are
coarse-grained, using LIST-LENGTH-DOTTED, etc.

My preliminary results suggest that this approach may be inferior to a
simple-minded check for NIL applied at every CAR and CDR even if the
input tree structure is in fact no broader than the destructuring
pattern.

If the input structure is larger, those length functions will waste a
lot of time traversing it. And anyway, the length functions still have
to check for NIL at every CDR operation. Their advantage is that they
do it in a loop, rather than unrolled inline code, which caches better.


Anyway, let me sign off with the kicker ...

(setf *print-circle* t)

(dstr:bind (a b c d e . f) '#1=(1 2 3 4 5 . #1#) (list a b c d e f))

-->

(1 2 3 4 5 #1=(1 2 3 4 5 . #1#))

Cheers ... :)
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1140943076.358814.324650@u72g2000cwu.googlegroups.com>
By the way, when I was out running, I thought of something.

A destructuring pattern can contain CAR leaves which are NIL. It's
possible that a structure mismatch will occur against these, even
though no value is being pulled out for a variable.

This should be allowed:

  (destructuring-bind (() a b c) (list 1 2 3 4))

The 1 in the data is matched by () which is the atom NIL, of course.
Atom against atom is valid!

Wouldn't you know it, this fails on CLISP! Should it?

NIL is a valid inner lambda list. A destructuring lambda list may be
empty. According to 3.4.5, it has the syntax:

  lambda-list::= (wholevar reqvars optvars restvar keyvars auxvars) |
                 (wholevar reqvars optvars . var)

All of the parts are optional. In particular

  reqvars::= var*

3.4.4.1 tells us that:

  Anywhere in a macro lambda list where a parameter name can appear,
  and where ordinary lambda list syntax (as described in Section 3.4.1
  (Ordinary Lambda Lists)) does not otherwise allow a list, a
destructuring
  lambda list can appear in place of the parameter name. When this is
  done, then the argument that would match the parameter is treated as
  a (possibly dotted) list, to be used as an argument list for
satisfying
  the parameters in the embedded lambda list. This is known
  as destructuring."

In other words, the match between () and 1 in is at the heart of
destructuring. It's the second simplest case! The simplest possible
list appears in place of a parameter name, and it's matched by the
simplest possible dotted list: a lone atom. The lambda list has no
parameters to satisfy, and so the terminating atom 1 is ignored. That
is that.

And this actually gives us something the lack of which Lisp programmers
sometimes bemoan: a way to indicate pieces of the input that are to be
ignored rather than bound to variables:

The simple DSTR:BIND I posted does this just fine:

  ;; take first and fourth, ignore second and third!
  (dstr:bind (a () () c) (list 1 2 3 4) (list a c))

   --> (1 4)

AFAIC, any implementation which breaks on this is wrong.

But on the other hand, this is a destructuring mismatch:

  (destructuring-bind ((()) a b c) (list 1 2 3 4))

Now 1 is being matched against (NIL). Atom against cons: error.
From: Pascal Bourguignon
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <874q2m9gb2.fsf@thalassa.informatimago.com>
"Kaz Kylheku" <········@gmail.com> writes:

> By the way, when I was out running, I thought of something.
>
> A destructuring pattern can contain CAR leaves which are NIL. It's
> possible that a structure mismatch will occur against these, even
> though no value is being pulled out for a variable.
>
> This should be allowed:
>
>   (destructuring-bind (() a b c) (list 1 2 3 4))
>
> The 1 in the data is matched by () which is the atom NIL, of course.
> Atom against atom is valid!
>
> Wouldn't you know it, this fails on CLISP! Should it?

IMO, yes.


> NIL is a valid inner lambda list. A destructuring lambda list may be
> empty. According to 3.4.5, it has the syntax:
> [...]

But anyways, you cannot bind cl:nil (neither cl:t or any other constant in CL).
So I'm not surprised if destructuring-bind makes no effort to try. 
(It could report a better error, I agree).


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

The world will now reboot.  don't bother saving your artefacts.
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1140985620.763792.137420@z34g2000cwc.googlegroups.com>
Pascal Bourguignon wrote:
> "Kaz Kylheku" <········@gmail.com> writes:
>
> > By the way, when I was out running, I thought of something.
> >
> > A destructuring pattern can contain CAR leaves which are NIL. It's
> > possible that a structure mismatch will occur against these, even
> > though no value is being pulled out for a variable.
> >
> > This should be allowed:
> >
> >   (destructuring-bind (() a b c) (list 1 2 3 4))
> >
> > The 1 in the data is matched by () which is the atom NIL, of course.
> > Atom against atom is valid!
> >
> > Wouldn't you know it, this fails on CLISP! Should it?
>
> IMO, yes.

Why?

>
> > NIL is a valid inner lambda list. A destructuring lambda list may be
> > empty. According to 3.4.5, it has the syntax:
> > [...]
>
> But anyways, you cannot bind cl:nil (neither cl:t or any other constant in CL).
> So I'm not surprised if destructuring-bind makes no effort to try.

But CL:NIL is also an empty list. In a destructuring lambda list, a
list is allowed in place of a variable, and it is taken to be an inner
destructuring pattern. The outer pattern can be empty according to the
grammar. So why not the inner one?

Where is it forbidden?
From: Rob Warnock
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <mtOdnfrkXYwZzp_ZnZ2dnUVZ_vydnZ2d@speakeasy.net>
Kaz Kylheku <········@gmail.com> wrote:
+---------------
| Pascal Bourguignon wrote:
| > "Kaz Kylheku" <········@gmail.com> writes:
| > > This should be allowed:
| > >   (destructuring-bind (() a b c) (list 1 2 3 4))
| > > The 1 in the data is matched by () which is the atom NIL, of course.
| > > Atom against atom is valid!
| > > Wouldn't you know it, this fails on CLISP! Should it?
| >
| > IMO, yes.
| 
| Why?
+---------------

Maybe because LISTP trumps SYMBOLP in the patterns?

CMUCL also barfs on that example, *not* because of the NIL in the
template, but because:

    Error while parsing arguments to DESTRUCTURING-BIND in "Top-Level Form":
    Bogus sublist:
      1
    to satisfy lambda-list:
      ()

However, if you feed CMUCL *this* it works just fine:

    > (destructuring-bind (() a b c) (list () 2 3 4) (+ a b c))

    9
    > 

Note: An old version of CLISP (2.29) also barfs on the latter,
with the message:

    *** - LET*: NIL is a constant, cannot be bound

I don't know what current versions give.


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1141005780.853072.40470@u72g2000cwu.googlegroups.com>
Rob Warnock wrote:
> CMUCL also barfs on that example, *not* because of the NIL in the
> template, but because:
>
>     Error while parsing arguments to DESTRUCTURING-BIND in "Top-Level Form":
>     Bogus sublist:
>       1
>     to satisfy lambda-list:
>       ()

Now where in the HyperSpec is this error permitted in place of robust
behavior? 1 is not a bogus sublist! It's a perfectly good dotted-list
of length zero, terminated by the atom 1.

  (list-length-dotted 1) -> 0

  (append '(3 2) 1) -> (3 2 . 1)

Although no variable binding is set up by the lambda list NIL, that
tree structure is compatible with the object 1, so there is no
destructuring mismatch. The right hand side just has to have all he
conses in the same configuration as the left, plus perhaps additional
conses. A tree structure is defined as a set of conses. The trees NIL
and 1 are both empty sets of conses. In other words, they are
/equivalent/ tree structures
> However, if you feed CMUCL *this* it works just fine:
>
>     > (destructuring-bind (() a b c) (list () 2 3 4) (+ a b c))

NIL can be matched by NIL. Good, but too strong, by itself.

>     9
>     >
>
> Note: An old version of CLISP (2.29) also barfs on the latter,
> with the message:
>
>     *** - LET*: NIL is a constant, cannot be bound
>
> I don't know what current versions give.

Something outlandish:

*** - SYSTEM::EMPTY-PATTERN: symbol SYSTEM::%NULL-TESTS has no value
From: Joerg Hoehle
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <uek1mjdoj.fsf@users.sourceforge.net>
"Kaz Kylheku" <········@gmail.com> writes:
> Rob Warnock wrote:
> >     > (destructuring-bind (() a b c) (list () 2 3 4) (+ a b c))
> 
> NIL can be matched by NIL. Good, but too strong, by itself.

> > Note: An old version of CLISP (2.29) also barfs on the latter,
> > with the message:
> >     *** - LET*: NIL is a constant, cannot be bound
> > I don't know what current versions give.
> Something outlandish:
> *** - SYSTEM::EMPTY-PATTERN: symbol SYSTEM::%NULL-TESTS has no value

Fixed today in CVS. Thanks for noting. NIL should have matched NIL
since mid-2004.  It did so within macro destructuring but forgot to
update DESTRUCTURING-BIND.
Now
(destructuring-bind (() a b c) (list () 2 3 4) (+ a b c))
has value 9 (also added testcase).


> Joerg Hoehle wrote:
> > I see no inconsistency.
> The inconsistency in that implementation is that
>  (a b)  is permitted to match (1 2 . 3) without error
Not in CLISP.
> yet
>  (a nil b)  does not match (1 2 3)
It does not match in CLISP.

So with the bug fixed, there is no more inconsistency (if it ever was
in CLISP) or is there anything else I missed?

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Pascal Bourguignon
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <87lkvx8tv0.fsf@thalassa.informatimago.com>
"Kaz Kylheku" <········@gmail.com> writes:

> Pascal Bourguignon wrote:
>> "Kaz Kylheku" <········@gmail.com> writes:
>>
>> > By the way, when I was out running, I thought of something.
>> >
>> > A destructuring pattern can contain CAR leaves which are NIL. It's
>> > possible that a structure mismatch will occur against these, even
>> > though no value is being pulled out for a variable.
>> >
>> > This should be allowed:
>> >
>> >   (destructuring-bind (() a b c) (list 1 2 3 4))
>> >
>> > The 1 in the data is matched by () which is the atom NIL, of course.
>> > Atom against atom is valid!
>> >
>> > Wouldn't you know it, this fails on CLISP! Should it?
>>
>> IMO, yes.
>
> Why?

Because () can only match (), and otherwise NIL cannot be bound.


>> > NIL is a valid inner lambda list. A destructuring lambda list may be
>> > empty. According to 3.4.5, it has the syntax:
>> > [...]
>>
>> But anyways, you cannot bind cl:nil (neither cl:t or any other constant in CL).
>> So I'm not surprised if destructuring-bind makes no effort to try.
>
> But CL:NIL is also an empty list. In a destructuring lambda list, a
> list is allowed in place of a variable, and it is taken to be an inner
> destructuring pattern. The outer pattern can be empty according to the
> grammar. So why not the inner one?
>
> Where is it forbidden?

Yes, of course. The only thing () can match is ().

(destructuring-bind (a () b) (list 1 nil 2) (values a b)) --> 1 ; 2


Note that in:

 (destructuring-bind (a b) '(1 2) (values a b))

there's an implicit match of () by ():

 (destructuring-bind (a b) '(1 2) (values a b))

is actually:

 (destructuring-bind (a . (b . ())) '(1 . (2 . ())) (values a b))


 (destructuring-bind (a b) '(1 2 3) (values a b))

gives an error, of course.

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

PUBLIC NOTICE AS REQUIRED BY LAW: Any use of this product, in any
manner whatsoever, will increase the amount of disorder in the
universe. Although no liability is implied herein, the consumer is
warned that this process will ultimately lead to the heat death of
the universe.
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1141008917.850902.59650@i39g2000cwa.googlegroups.com>
Pascal Bourguignon wrote:
> Note that in:
>
>  (destructuring-bind (a b) '(1 2) (values a b))
>
> there's an implicit match of () by ():

Note that in

 (destructuring-bind (a b) '(1 2 . 3) (values a b))

There is an implicit match of () by 3.

If your implementation rejects it in one situation but not in another,
it's inconsistent.

() is a proper list of length 0. 3 is an improper list of length 0.
LIST-LENGTH-DOTTED and APPEND agree:

  (list-length-dotted 3) --> 0

  (append '(1 2) 3) --> (1 2 3)

But you know what? I just found this at the bottom of 3.4.4:

  It is permissible for a macro form (or a subexpression of a macro
  form) to be a dotted list only when (... &rest var) or (... . var)
  is used to match it. It is the responsibility of the macro to
  recognize and deal with such situations.

For general destructuring, pretend that "macro form" is the "tree
structure to be destructured".

So in fact

  (destructuring-bind (a b) '(1 2 . 3))

is an error according to this.

That text is written because the tree-structure compatibility rules do
not rule this out! The terminating atom NIL in the pattern is just a
leaf, which could match anything in the data (other than a cons!!!)

And so, there we have the rule which rejects the matching of () against
1. The only list which can match it is (&rest var), which is just a
synonym for var.

So, to recap:

1. A tree structure is defined as a set of conses. The car objects are
   excluded from the tree structure unless they are conses. So
   two tree structures are equivalent if they have this same cons
   structure. cdr objects are not excluded from the tree structure, so
   improper lists with different terminating atoms are not equivalent.
2. A compatible tree structure for a destructuring pattern
   is either equivalent, or it has some conses matching leaves in the
   pattern. (This rule leaves two gaping holes, addressed by 3 and 4).
3. A cdr that is other than NIL must be matched by a leaf atom that is
   a variable, not by NIL.  This disallows the NIL  versus 1 match.
4. If there is no dot or &rest, there can't be extra arguments to the
   lambda list (by 3.4.1.3).  Without this rule, 2. allows a
   terminating NIL leaf to match a non-atomic object in the macro
   form or destructuring data, so (a b) can match (1 2 3).
   This is a rule inherited from ordinary lambda lists.
From: Joerg Hoehle
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <uvev0k8gn.fsf@users.sourceforge.net>
"Kaz Kylheku" <········@gmail.com> writes:
> Note that in
>  (destructuring-bind (a b) '(1 2 . 3) (values a b))
> There is an implicit match of () by 3.
No. As you yourself point out,
> But you know what? I just found this at the bottom of 3.4.4:
>   It is permissible for a macro form (or a subexpression of a macro
>   form) to be a dotted list only when (... &rest var) or (... . var)
>   is used to match it. It is the responsibility of the macro to
>   recognize and deal with such situations.
your example is *not* in so-called dotted context.

> So in fact
>   (destructuring-bind (a b) '(1 2 . 3))
> is an error according to this.
Indeed.

Generally, I welcome that you try to add semantics to the NIL pattern,
(esp. since it's otherwise somewhat useless, nil being a constant
variable).  People have repeatedly asked for such a thing (and
e.g. the Iterate package does it[*]).

However, I argue that it has never been CL's intent to allow for such
a use.  Loose hint in CLHS supporting my claim are:

If it had intended to be so, there would have been examples, if not an
extra paragraph allowing this.  Why so? because the authors of ANSI-CL
must have been aware of the phenomenon.  There existed packages old
enough that featured the "NIL pattern matches anything" long ago.
Destructuring-bind is not among those.


Indeed Iterate handles NIL as you require�(but it's only ~1990)
E.g. (dsetq (nil a b) ...) matches (1 2 3)
and  (dsetq (a . nil) == (a) matches (1 2 3) as well...
Uhoh, I did not anticipate this.

> If your implementation rejects it in one situation but not in another,
> it's inconsistent.
I see no inconsistency.

Yet I agree with you that
(destructuring-bind (a . b) <infinite-list> body)
should not yield an error.  I'll try to see how clisp can be modified
to accept this without breaking the other situations.


> So, to recap: [...]
I'm lost :-)

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1141073000.761836.82150@u72g2000cwu.googlegroups.com>
Joerg Hoehle wrote:
> "Kaz Kylheku" <········@gmail.com> writes:
> > Note that in
> >  (destructuring-bind (a b) '(1 2 . 3) (values a b))
> > There is an implicit match of () by 3.
> No. As you yourself point out,
> > But you know what? I just found this at the bottom of 3.4.4:
> >   It is permissible for a macro form (or a subexpression of a macro
> >   form) to be a dotted list only when (... &rest var) or (... . var)
> >   is used to match it. It is the responsibility of the macro to
> >   recognize and deal with such situations.
> your example is *not* in so-called dotted context.

Exactly! I understand that now. Those words above are why

  (a b () c)    (1 2 3 4)

is a destructuring mismatch.

The dotted list 3 of zero length must /not/ match the proper list NIL
of zero length even though their structure is compatible.

In fact (a b)   (1 2 3)  have compatible tree structure also. What
rules out the match is the restriction written for ordinary lambda
lists: the number of actual arguments can't exceed the number of
required ones if there is no &rest to catch the extra ones.

Without that rule, the leaf atom NIL which terminates (a b) could match
a non-atomic object in (1 2 3), namely the (3) cons.



> > So in fact
> >   (destructuring-bind (a b) '(1 2 . 3))
> > is an error according to this.
> Indeed.
>
> Generally, I welcome that you try to add semantics to the NIL pattern,
> (esp. since it's otherwise somewhat useless, nil being a constant
> variable).  People have repeatedly asked for such a thing (and
> e.g. the Iterate package does it[*]).

I think that it would perhaps be better, as an extension, to have a
special keyword.

Perhaps borrowing the existing keyword :WILD from the Filenames
library.

Examples

  (a :wild c)   ;; matches (1 2 3)

  (a c . :wild)  ;; matches (1 2 . <any cons or atom>)

  (a c &rest :wild)  ;; same as above


> However, I argue that it has never been CL's intent to allow for such
> a use.  Loose hint in CLHS supporting my claim are:
>
> If it had intended to be so, there would have been examples, if not an
> extra paragraph allowing this.  Why so? because the authors of ANSI-CL
> must have been aware of the phenomenon.  There existed packages old
> enough that featured the "NIL pattern matches anything" long ago.
> Destructuring-bind is not among those.
>
>
> Indeed Iterate handles NIL as you require´(but it's only ~1990)
> E.g. (dsetq (nil a b) ...) matches (1 2 3)
> and  (dsetq (a . nil) == (a) matches (1 2 3) as well...
> Uhoh, I did not anticipate this.
>
> > If your implementation rejects it in one situation but not in another,
> > it's inconsistent.
> I see no inconsistency.

The inconsistency in that implementation is that

 (a b)  is permitted to match (1 2 . 3) without error

yet

 (a nil b)  does not match (1 2 3)

Both are are violations of the same rule: proper list pattern of length
N matched against improper list data of length N.

> Yet I agree with you that
> (destructuring-bind (a . b) <infinite-list> body)
> should not yield an error.  I'll try to see how clisp can be modified
> to accept this without breaking the other situations.

I have everything working except for &aux and 50% of &key. (I'm as far
as having a function which parses out the &key specifiers and returns
three values: a canonicalized form of the specifiers, the remaining
&aux material, if any, and a third boolean value which indicates
whether an &allow-other-keys was scanned).
From: Joerg Hoehle
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <uu09sazvy.fsf@users.sourceforge.net>
"Kaz Kylheku" <········@gmail.com> writes:
> I have everything working except for &aux and 50% of &key. (I'm as far
> as having a function which parses out the &key specifiers and returns
> three values: a canonicalized form of the specifiers, the remaining
> &aux material, if any, and a third boolean value which indicates
> whether an &allow-other-keys was scanned).

It came to my mind that there's a problem with your favourite nested
LET approach and declarations.  Did you think about that?

(destructuring-bind (a b c) foo
  (declare ...)
  body)
is different from (error-checking not shown):
(let* ((cons1 foo) (a (car cons1)))
  (let* ((cons2 (cdr cons2)) (b (car cons2)))
    (let* ((cons3 ...))
      (declare <unchanged-from-above>)
      body)))

E.g. consider effects of (declare (special b))
Correct handling would require walking declarations (eek) and possibly
splitting them.  I don't know how to portably walk declarations as I
can't portably recognize short-form type specifiers, e.g.
(declare (some-type var)) instead of
(declare (type some-type var))

Regards,
	Jorg Hohle
Telekom/T-Systems Technology Center
From: Kaz Kylheku
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <1142956650.937585.12760@i40g2000cwc.googlegroups.com>
Joerg Hoehle wrote:
> "Kaz Kylheku" <········@gmail.com> writes:
> > I have everything working except for &aux and 50% of &key. (I'm as far
> > as having a function which parses out the &key specifiers and returns
> > three values: a canonicalized form of the specifiers, the remaining
> > &aux material, if any, and a third boolean value which indicates
> > whether an &allow-other-keys was scanned).
>
> It came to my mind that there's a problem with your favourite nested
> LET approach and declarations.  Did you think about that?

Of course. The bind doesn't work that way. It doesn't nest a bunch of
lets, but gathers up the var init forms for one giant LET*.

> (destructuring-bind (a b c) foo
>   (declare ...)
>   body)
> is different from (error-checking not shown):
> (let* ((cons1 foo) (a (car cons1)))
>   (let* ((cons2 (cdr cons2)) (b (car cons2)))
>     (let* ((cons3 ...))
>       (declare <unchanged-from-above>)
>       body)))

That's right; an obvious "non-starter".

Here is an example output. Note that there is incomplete support for
checking that the input doesn't contain superfluous elements:

(macroexpand-1 '(dstr:bind (a ((b c) d) e f) '(1 ((2 3) 4) 5 6)))

->

(LET*
 ((#:G2992 '(1 ((2 3) 4) 5 6))
  (#:G2993 (DSTR::ERR-CAR '(A ((B C) D) E F) #:G2992)) (A #:G2993)
  (#:G2994 (DSTR::ERR-CDR '(A ((B C) D) E F) #:G2992))
  (#:G2995 (DSTR::ERR-CAR '(((B C) D) E F) #:G2994))
  (#:G2997 (DSTR::ERR-CAR '((B C) D) #:G2995))
  (#:G2999 (DSTR::ERR-CAR '(B C) #:G2997)) (B #:G2999)
  (#:G3000 (DSTR::ERR-CDR '(B C) #:G2997))
  (#:G3001 (DSTR::ERR-CAR '(C) #:G3000)) (C #:G3001)
  (#:G3002 (DSTR::ERR-CDR '(C) #:G3000))
  (#:G2998 (DSTR::ERR-CDR '((B C) D) #:G2995))
  (#:G3003 (DSTR::ERR-CAR '(D) #:G2998)) (D #:G3003)
  (#:G3004 (DSTR::ERR-CDR '(D) #:G2998))
  (#:G2996 (DSTR::ERR-CDR '(((B C) D) E F) #:G2994))
  (#:G3005 (DSTR::ERR-CAR '(E F) #:G2996)) (E #:G3005)
  (#:G3006 (DSTR::ERR-CDR '(E F) #:G2996))
  (#:G3007 (DSTR::ERR-CAR '(F) #:G3006)) (F #:G3007)
  (#:G3008 (DSTR::ERR-CDR '(F) #:G3006)))) ;

The pieces of the pattern like ((B C) D) passed to the DSTR:ERR-*
functions is for the purpose of emitting a nice error message. ERR-CAR
and ERR-CDR signal if their argument isn't a cons.

The destructuring errors can be caught at the ends of lists, rather
than using some dotted length function upfront.

Note that the last #:G3008 (unused) variable for instance should be
NIL.  If it's some other atom, then the input list is dotted, which is
a destructuring error. If it's a cons, then the list is longer, a
destructuring error.

The check is easy to add, but it would be nice to have more context for
it. One way would be to use special variables. Whenever the expander
starts processing a list or sublist pattern, it could bind a special
variable to that list, then when it recursively CDRs down to the end of
that sublist and finds an error, it can look at that variable to get
the pattern for the error message.
From: Brian Downing
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <sX4Nf.828823$xm3.740332@attbi_s21>
In article <·······················@i39g2000cwa.googlegroups.com>,
Kaz Kylheku <········@gmail.com> wrote:
> () is a proper list of length 0. 3 is an improper list of length 0.
> LIST-LENGTH-DOTTED and APPEND agree:
> 
>   (list-length-dotted 3) --> 0

LIST-LENGTH-DOTTED is not in Common Lisp.  However, this is:

dotted list n. a list which has a terminating atom that is not nil. (An
               atom by itself is not a dotted list, however.)

Further, an improper list is defined to be a list (either circular or
dotted), and a list is defined to be a chain of conses, which clearly
3 isn't.

>   (append '(1 2) 3) --> (1 2 3)

APPEND specifically says:

append &rest lists => result
Arguments and Values:
list---each must be a proper list except the last, which may be any
object.

So just because something will go in the last argument of append doesn't
mean it's some kind of list.

-bcd
-- 
*** Brian Downing <bdowning at lavos dot net> 
From: Brian Downing
Subject: Re: destructuring-bind on infinite lists?
Date: 
Message-ID: <L25Nf.828837$xm3.261468@attbi_s21>
In article <·······················@attbi_s21>,
Brian Downing  <·············@lavos.net> wrote:
> In article <·······················@i39g2000cwa.googlegroups.com>,
> Kaz Kylheku <········@gmail.com> wrote:
> > () is a proper list of length 0. 3 is an improper list of length 0.
> > LIST-LENGTH-DOTTED and APPEND agree:
> > 
> >   (list-length-dotted 3) --> 0
> 
> LIST-LENGTH-DOTTED is not in Common Lisp.  However, this is:
> 
> dotted list n. a list which has a terminating atom that is not nil. (An
>                atom by itself is not a dotted list, however.)
> 
> Further, an improper list is defined to be a list (either circular or
> dotted), and a list is defined to be a chain of conses, which clearly
> 3 isn't.

There's also an issue writeup that concerns this:

http://www.lispworks.com/documentation/HyperSpec/Issues/iss138_w.htm

-bcd
-- 
*** Brian Downing <bdowning at lavos dot net>